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_user.F90 in branches/2017/dev_merge_2017/NEMOGCM/NEMO/NST_SRC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 @ 9449

Last change on this file since 9449 was 9449, checked in by smasson, 6 years ago

dev_merge_2017: agrif bugfix for non-constant jpi/jpj + some cleaning...

  • Property svn:keywords set to Id
File size: 35.7 KB
Line 
1#undef UPD_HIGH   /* MIX HIGH UPDATE */
2#if defined key_agrif
3!!----------------------------------------------------------------------
4!! NEMO/NST 4.0 , NEMO Consortium (2017)
5!! $Id$
6!! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
7!!----------------------------------------------------------------------
8SUBROUTINE agrif_user
9END SUBROUTINE agrif_user
10
11SUBROUTINE agrif_before_regridding
12END SUBROUTINE agrif_before_regridding
13
14SUBROUTINE Agrif_InitWorkspace
15   !!----------------------------------------------------------------------
16   !!                 *** ROUTINE Agrif_InitWorkspace ***
17   !!----------------------------------------------------------------------
18   USE par_oce
19   USE dom_oce
20   USE nemogcm
21   USE mppini
22   !!
23   IMPLICIT NONE
24   !!----------------------------------------------------------------------
25   !
26   IF( .NOT. Agrif_Root() ) THEN
27      ! no more static variables
28!!$! JC: change to allow for different vertical levels
29!!$!     jpk is already set
30!!$!     keep it jpk possibly different from jpkglo which
31!!$!     hold parent grid vertical levels number (set earlier)
32!!$!      jpk     = jpkglo
33   ENDIF
34   !
35END SUBROUTINE Agrif_InitWorkspace
36
37
38SUBROUTINE Agrif_InitValues
39   !!----------------------------------------------------------------------
40   !!                 *** ROUTINE Agrif_InitValues ***
41   !!
42   !! ** Purpose :: Declaration of variables to be interpolated
43   !!----------------------------------------------------------------------
44   USE Agrif_Util
45   USE oce 
46   USE dom_oce
47   USE nemogcm
48   USE tradmp
49   USE bdy_oce   , ONLY: ln_bdy
50   !!
51   IMPLICIT NONE
52   !!----------------------------------------------------------------------
53   !
54   CALL nemo_init       !* Initializations of each fine grid
55
56   !                    !* Agrif initialization
57   CALL agrif_nemo_init
58   CALL Agrif_InitValues_cont_dom
59   CALL Agrif_InitValues_cont
60# if defined key_top
61   CALL Agrif_InitValues_cont_top
62# endif
63# if defined key_lim3
64   CALL Agrif_InitValues_cont_lim3
65# endif
66   !
67   IF ( Agrif_Level().EQ.Agrif_MaxLevel() ) CALL agrif_Update_ini()
68
69   Agrif_UseSpecialValueInUpdate = .FALSE.     
70
71END SUBROUTINE Agrif_initvalues
72
73
74SUBROUTINE Agrif_InitValues_cont_dom
75   !!----------------------------------------------------------------------
76   !!                 *** ROUTINE Agrif_InitValues_cont ***
77   !!
78   !! ** Purpose ::   Declaration of variables to be interpolated
79   !!----------------------------------------------------------------------
80   USE Agrif_Util
81   USE oce 
82   USE dom_oce
83   USE nemogcm
84   USE in_out_manager
85   USE agrif_opa_update
86   USE agrif_opa_interp
87   USE agrif_opa_sponge
88   !
89   IMPLICIT NONE
90   !!----------------------------------------------------------------------
91   !
92   ! Declaration of the type of variable which have to be interpolated
93   !
94   CALL agrif_declare_var_dom
95   !
96END SUBROUTINE Agrif_InitValues_cont_dom
97
98
99SUBROUTINE agrif_declare_var_dom
100   !!----------------------------------------------------------------------
101   !!                 *** ROUTINE agrif_declare_var ***
102   !!
103   !! ** Purpose :: Declaration of variables to be interpolated
104   !!----------------------------------------------------------------------
105   USE agrif_util
106   USE par_oce       
107   USE oce
108   !
109   IMPLICIT NONE
110   !
111   INTEGER :: ind1, ind2, ind3
112   !!----------------------------------------------------------------------
113
114   ! 1. Declaration of the type of variable which have to be interpolated
115   !---------------------------------------------------------------------
116   ind1 =     nbghostcells
117   ind2 = 1 + nbghostcells
118   ind3 = 2 + nbghostcells
119   CALL agrif_declare_variable((/1,2/),(/ind2,ind3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),e1u_id)
120   CALL agrif_declare_variable((/2,1/),(/ind3,ind2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),e2v_id)
121
122   ! 2. Type of interpolation
123   !-------------------------
124   CALL Agrif_Set_bcinterp( e1u_id, interp1=Agrif_linear, interp2=AGRIF_ppm    )
125   CALL Agrif_Set_bcinterp( e2v_id, interp1=AGRIF_ppm   , interp2=Agrif_linear )
126
127   ! 3. Location of interpolation
128   !-----------------------------
129   CALL Agrif_Set_bc(e1u_id,(/0,ind1-1/))
130   CALL Agrif_Set_bc(e2v_id,(/0,ind1-1/))
131
132   ! 4. Update type
133   !---------------
134# if defined UPD_HIGH
135   CALL Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Full_Weighting)
136   CALL Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Full_Weighting, update2=Agrif_Update_Average)
137#else
138   CALL Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average)
139   CALL Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy)
140#endif
141
142END SUBROUTINE agrif_declare_var_dom
143
144
145SUBROUTINE Agrif_InitValues_cont
146   !!----------------------------------------------------------------------
147   !!                 *** ROUTINE Agrif_InitValues_cont ***
148   !!
149   !! ** Purpose ::   Declaration of variables to be interpolated
150   !!----------------------------------------------------------------------
151   USE agrif_opa_update
152   USE agrif_opa_interp
153   USE agrif_opa_sponge
154   USE Agrif_Util
155   USE oce 
156   USE dom_oce
157   USE zdf_oce
158   USE nemogcm
159   !
160   USE lib_mpp
161   USE in_out_manager
162   !
163   IMPLICIT NONE
164   !
165   LOGICAL :: check_namelist
166   CHARACTER(len=15) :: cl_check1, cl_check2, cl_check3, cl_check4 
167   !!----------------------------------------------------------------------
168
169   ! 1. Declaration of the type of variable which have to be interpolated
170   !---------------------------------------------------------------------
171   CALL agrif_declare_var
172
173   ! 2. First interpolations of potentially non zero fields
174   !-------------------------------------------------------
175   Agrif_SpecialValue    = 0._wp
176   Agrif_UseSpecialValue = .TRUE.
177   CALL Agrif_Bc_variable(tsn_id,calledweight=1.,procname=interptsn)
178   CALL Agrif_Sponge
179   tabspongedone_tsn = .FALSE.
180   CALL Agrif_Bc_variable(tsn_sponge_id,calledweight=1.,procname=interptsn_sponge)
181   ! reset tsa to zero
182   tsa(:,:,:,:) = 0.
183
184   Agrif_UseSpecialValue = ln_spc_dyn
185   CALL Agrif_Bc_variable(un_interp_id,calledweight=1.,procname=interpun)
186   CALL Agrif_Bc_variable(vn_interp_id,calledweight=1.,procname=interpvn)
187   tabspongedone_u = .FALSE.
188   tabspongedone_v = .FALSE.
189   CALL Agrif_Bc_variable(un_sponge_id,calledweight=1.,procname=interpun_sponge)
190   tabspongedone_u = .FALSE.
191   tabspongedone_v = .FALSE.
192   CALL Agrif_Bc_variable(vn_sponge_id,calledweight=1.,procname=interpvn_sponge)
193
194   Agrif_UseSpecialValue = .TRUE.
195   CALL Agrif_Bc_variable(sshn_id,calledweight=1., procname=interpsshn )
196   hbdy_w(:,:) = 0.e0 ; hbdy_e(:,:) = 0.e0 ; hbdy_n(:,:) = 0.e0 ; hbdy_s(:,:) = 0.e0
197   ssha(:,:) = 0.e0
198
199   IF ( ln_dynspg_ts ) THEN
200      Agrif_UseSpecialValue = ln_spc_dyn
201      CALL Agrif_Bc_variable(unb_id,calledweight=1.,procname=interpunb)
202      CALL Agrif_Bc_variable(vnb_id,calledweight=1.,procname=interpvnb)
203      CALL Agrif_Bc_variable(ub2b_interp_id,calledweight=1.,procname=interpub2b)
204      CALL Agrif_Bc_variable(vb2b_interp_id,calledweight=1.,procname=interpvb2b)
205      ubdy_w(:,:) = 0.e0 ; vbdy_w(:,:) = 0.e0
206      ubdy_e(:,:) = 0.e0 ; vbdy_e(:,:) = 0.e0
207      ubdy_n(:,:) = 0.e0 ; vbdy_n(:,:) = 0.e0
208      ubdy_s(:,:) = 0.e0 ; vbdy_s(:,:) = 0.e0
209   ENDIF
210
211   Agrif_UseSpecialValue = .FALSE. 
212   ! reset velocities to zero
213   ua(:,:,:) = 0.
214   va(:,:,:) = 0.
215
216   ! 3. Some controls
217   !-----------------
218   check_namelist = .TRUE.
219
220   IF( check_namelist ) THEN 
221
222      ! Check time steps           
223      IF( NINT(Agrif_Rhot()) * NINT(rdt) .NE. Agrif_Parent(rdt) ) THEN
224         WRITE(cl_check1,*)  NINT(Agrif_Parent(rdt))
225         WRITE(cl_check2,*)  NINT(rdt)
226         WRITE(cl_check3,*)  NINT(Agrif_Parent(rdt)/Agrif_Rhot())
227         CALL ctl_stop( 'Incompatible time step between ocean grids',   &
228               &               'parent grid value : '//cl_check1    ,   & 
229               &               'child  grid value : '//cl_check2    ,   & 
230               &               'value on child grid should be changed to : '//cl_check3 )
231      ENDIF
232
233      ! Check run length
234      IF( Agrif_IRhot() * (Agrif_Parent(nitend)- &
235            Agrif_Parent(nit000)+1) .NE. (nitend-nit000+1) ) THEN
236         WRITE(cl_check1,*)  (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1
237         WRITE(cl_check2,*)   Agrif_Parent(nitend)   *Agrif_IRhot()
238         CALL ctl_warn( 'Incompatible run length between grids'                      ,   &
239               &               'nit000 on fine grid will be changed to : '//cl_check1,   &
240               &               'nitend on fine grid will be changed to : '//cl_check2    )
241         nit000 = (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1
242         nitend =  Agrif_Parent(nitend)   *Agrif_IRhot()
243      ENDIF
244
245      ! Check free surface scheme
246      IF ( ( Agrif_Parent(ln_dynspg_ts ).AND.ln_dynspg_exp ).OR.&
247         & ( Agrif_Parent(ln_dynspg_exp).AND.ln_dynspg_ts ) ) THEN
248         WRITE(cl_check1,*)  Agrif_Parent( ln_dynspg_ts )
249         WRITE(cl_check2,*)  ln_dynspg_ts
250         WRITE(cl_check3,*)  Agrif_Parent( ln_dynspg_exp )
251         WRITE(cl_check4,*)  ln_dynspg_exp
252         CALL ctl_stop( 'Incompatible free surface scheme between grids' ,  &
253               &               'parent grid ln_dynspg_ts  :'//cl_check1  ,  & 
254               &               'child  grid ln_dynspg_ts  :'//cl_check2  ,  &
255               &               'parent grid ln_dynspg_exp :'//cl_check3  ,  &
256               &               'child  grid ln_dynspg_exp :'//cl_check4  ,  &
257               &               'those logicals should be identical' )                 
258         STOP
259      ENDIF
260
261      ! Check if identical linear free surface option
262      IF ( ( Agrif_Parent(ln_linssh ).AND.(.NOT.ln_linssh )).OR.&
263         & ( (.NOT.Agrif_Parent(ln_linssh)).AND.ln_linssh ) ) THEN
264         WRITE(cl_check1,*)  Agrif_Parent(ln_linssh )
265         WRITE(cl_check2,*)  ln_linssh
266         CALL ctl_stop( 'Incompatible linearized fs option between grids',  &
267               &               'parent grid ln_linssh  :'//cl_check1     ,  &
268               &               'child  grid ln_linssh  :'//cl_check2     ,  &
269               &               'those logicals should be identical' )                 
270         STOP
271      ENDIF
272
273      ! check if masks and bathymetries match
274      IF(ln_chk_bathy) THEN
275         !
276         IF(lwp) WRITE(numout,*) 'AGRIF: Check Bathymetry and masks near bdys. Level: ', Agrif_Level()
277         !
278         kindic_agr = 0
279         ! check if umask agree with parent along western and eastern boundaries:
280         CALL Agrif_Bc_variable(umsk_id,calledweight=1.,procname=interpumsk)
281         ! check if vmask agree with parent along northern and southern boundaries:
282         CALL Agrif_Bc_variable(vmsk_id,calledweight=1.,procname=interpvmsk)
283         ! check if tmask and vertical scale factors agree with parent over first two coarse grid points:
284         CALL Agrif_Bc_variable(e3t_id,calledweight=1.,procname=interpe3t)
285         !
286         IF (lk_mpp) CALL mpp_sum( kindic_agr )
287         IF( kindic_agr /= 0 ) THEN
288            CALL ctl_stop('Child Bathymetry is not correct near boundaries.')
289         ELSE
290            IF(lwp) WRITE(numout,*) 'Child Bathymetry is ok near boundaries.'
291         END IF
292      ENDIF
293      !
294   ENDIF
295   !
296END SUBROUTINE Agrif_InitValues_cont
297
298RECURSIVE SUBROUTINE Agrif_Update_ini( )
299   !!----------------------------------------------------------------------
300   !!                 *** ROUTINE agrif_Update_ini ***
301   !!
302   !! ** Purpose :: Recursive update done at initialization
303   !!----------------------------------------------------------------------
304   USE dom_oce
305   USE agrif_opa_update
306#if defined key_top
307   USE agrif_top_update
308#endif
309   !
310   IMPLICIT NONE
311   !!----------------------------------------------------------------------
312   !
313   IF (Agrif_Root()) RETURN
314   !
315   CALL Agrif_Update_ssh()
316   IF (.NOT.ln_linssh) CALL Agrif_Update_vvl()
317   CALL Agrif_Update_tra()
318#if defined key_top
319   CALL Agrif_Update_Trc()
320#endif
321   CALL Agrif_Update_dyn()
322! JC remove update because this precludes from perfect restartability
323!!   CALL Agrif_Update_tke(0)
324
325   CALL Agrif_ChildGrid_To_ParentGrid()
326   CALL Agrif_Update_ini()
327   CALL Agrif_ParentGrid_To_ChildGrid()
328
329END SUBROUTINE agrif_update_ini
330
331SUBROUTINE agrif_declare_var
332   !!----------------------------------------------------------------------
333   !!                 *** ROUTINE agrif_declarE_var ***
334   !!
335   !! ** Purpose :: Declaration of variables to be interpolated
336   !!----------------------------------------------------------------------
337   USE agrif_util
338   USE agrif_oce
339   USE par_oce       ! ocean parameters
340   USE zdf_oce       ! vertical physics
341   USE oce
342   !
343   IMPLICIT NONE
344   !
345   INTEGER :: ind1, ind2, ind3
346   !!----------------------------------------------------------------------
347
348   ! 1. Declaration of the type of variable which have to be interpolated
349   !---------------------------------------------------------------------
350   ind1 =     nbghostcells
351   ind2 = 1 + nbghostcells
352   ind3 = 2 + nbghostcells
353# if defined key_vertical
354   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jpts+1/),tsn_id)
355   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jpts+1/),tsn_sponge_id)
356
357   CALL agrif_declare_variable((/1,2,0,0/),(/ind2,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),un_interp_id)
358   CALL agrif_declare_variable((/2,1,0,0/),(/ind3,ind2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),vn_interp_id)
359   CALL agrif_declare_variable((/1,2,0,0/),(/ind2,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),un_update_id)
360   CALL agrif_declare_variable((/2,1,0,0/),(/ind3,ind2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),vn_update_id)
361   CALL agrif_declare_variable((/1,2,0,0/),(/ind2,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),un_sponge_id)
362   CALL agrif_declare_variable((/2,1,0,0/),(/ind3,ind2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),vn_sponge_id)
363# else
364   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jpts/),tsn_id)
365   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jpts/),tsn_sponge_id)
366
367   CALL agrif_declare_variable((/1,2,0,0/),(/ind2,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),un_interp_id)
368   CALL agrif_declare_variable((/2,1,0,0/),(/ind3,ind2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),vn_interp_id)
369   CALL agrif_declare_variable((/1,2,0,0/),(/ind2,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),un_update_id)
370   CALL agrif_declare_variable((/2,1,0,0/),(/ind3,ind2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),vn_update_id)
371   CALL agrif_declare_variable((/1,2,0,0/),(/ind2,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),un_sponge_id)
372   CALL agrif_declare_variable((/2,1,0,0/),(/ind3,ind2,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),vn_sponge_id)
373# endif
374
375   CALL agrif_declare_variable((/2,2,0/),(/ind3,ind3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),e3t_id)
376   CALL agrif_declare_variable((/1,2,0/),(/ind2,ind3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),umsk_id)
377   CALL agrif_declare_variable((/2,1,0/),(/ind3,ind2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vmsk_id)
378
379   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,3/),scales_t_id)
380
381   CALL agrif_declare_variable((/1,2/),(/ind2,ind3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),unb_id)
382   CALL agrif_declare_variable((/2,1/),(/ind3,ind2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),vnb_id)
383   CALL agrif_declare_variable((/1,2/),(/ind2,ind3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),ub2b_interp_id)
384   CALL agrif_declare_variable((/2,1/),(/ind3,ind2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),vb2b_interp_id)
385   CALL agrif_declare_variable((/1,2/),(/ind2,ind3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),ub2b_update_id)
386   CALL agrif_declare_variable((/2,1/),(/ind3,ind2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),vb2b_update_id)
387
388   CALL agrif_declare_variable((/2,2/),(/ind3,ind3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),sshn_id)
389
390   IF( ln_zdftke.OR.ln_zdfgls ) THEN
391!      CALL agrif_declare_variable((/2,2,0/),(/ind3,ind3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/), en_id)
392!      CALL agrif_declare_variable((/2,2,0/),(/ind3,ind3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),avt_id)
393# if defined key_vertical
394      CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,2/),avm_id)
395# else
396      CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,1/),avm_id)
397# endif
398   ENDIF
399
400   ! 2. Type of interpolation
401   !-------------------------
402   CALL Agrif_Set_bcinterp(tsn_id,interp=AGRIF_linear)
403
404   CALL Agrif_Set_bcinterp(un_interp_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
405   CALL Agrif_Set_bcinterp(vn_interp_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
406
407   CALL Agrif_Set_bcinterp(tsn_sponge_id,interp=AGRIF_linear)
408
409   CALL Agrif_Set_bcinterp(sshn_id,interp=AGRIF_linear)
410   CALL Agrif_Set_bcinterp(unb_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
411   CALL Agrif_Set_bcinterp(vnb_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
412   CALL Agrif_Set_bcinterp(ub2b_interp_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
413   CALL Agrif_Set_bcinterp(vb2b_interp_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
414
415
416   CALL Agrif_Set_bcinterp(un_sponge_id,interp1=Agrif_linear,interp2=AGRIF_ppm)
417   CALL Agrif_Set_bcinterp(vn_sponge_id,interp1=AGRIF_ppm,interp2=Agrif_linear)
418
419   CALL Agrif_Set_bcinterp(e3t_id,interp=AGRIF_constant)
420   CALL Agrif_Set_bcinterp(umsk_id,interp=AGRIF_constant)
421   CALL Agrif_Set_bcinterp(vmsk_id,interp=AGRIF_constant)
422
423   IF( ln_zdftke.OR.ln_zdfgls )   CALL Agrif_Set_bcinterp( avm_id, interp=AGRIF_linear )
424
425   ! 3. Location of interpolation
426   !-----------------------------
427   CALL Agrif_Set_bc(       tsn_id, (/0,ind1/) )
428   CALL Agrif_Set_bc( un_interp_id, (/0,ind1/) )
429   CALL Agrif_Set_bc( vn_interp_id, (/0,ind1/) )
430
431   CALL Agrif_Set_bc( tsn_sponge_id, (/-nn_sponge_len*Agrif_irhox()-1,0/) )  ! if west and rhox=3 and sponge=2 and ghost=1: columns 2 to 9
432   CALL Agrif_Set_bc(  un_sponge_id, (/-nn_sponge_len*Agrif_irhox()-1,0/) )
433   CALL Agrif_Set_bc(  vn_sponge_id, (/-nn_sponge_len*Agrif_irhox()-1,0/) )
434
435   CALL Agrif_Set_bc(        sshn_id, (/0,ind1-1/) )
436   CALL Agrif_Set_bc(         unb_id, (/0,ind1-1/) )
437   CALL Agrif_Set_bc(         vnb_id, (/0,ind1-1/) )
438   CALL Agrif_Set_bc( ub2b_interp_id, (/0,ind1-1/) )
439   CALL Agrif_Set_bc( vb2b_interp_id, (/0,ind1-1/) )
440
441   CALL Agrif_Set_bc(  e3t_id, (/-2*Agrif_irhox()-1,ind1-1/) )   ! if west and rhox=3 and ghost=1: column 2 to 9
442   CALL Agrif_Set_bc( umsk_id, (/0,ind1-1/)                  )
443   CALL Agrif_Set_bc( vmsk_id, (/0,ind1-1/)                  )
444
445   IF( ln_zdftke.OR.ln_zdfgls )   CALL Agrif_Set_bc( avm_id, (/0,ind1/) )
446
447   ! 4. Update type
448   !---------------
449   CALL Agrif_Set_Updatetype(scales_t_id, update = AGRIF_Update_Average)
450
451# if defined UPD_HIGH
452   CALL Agrif_Set_Updatetype(tsn_id, update = Agrif_Update_Full_Weighting)
453   CALL Agrif_Set_Updatetype(un_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Full_Weighting)
454   CALL Agrif_Set_Updatetype(vn_update_id,update1 = Agrif_Update_Full_Weighting, update2 = Agrif_Update_Average)
455
456   CALL Agrif_Set_Updatetype(ub2b_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Full_Weighting)
457   CALL Agrif_Set_Updatetype(vb2b_update_id,update1 = Agrif_Update_Full_Weighting, update2 = Agrif_Update_Average)
458   CALL Agrif_Set_Updatetype(sshn_id, update = Agrif_Update_Full_Weighting)
459   CALL Agrif_Set_Updatetype(e3t_id, update = Agrif_Update_Full_Weighting)
460
461   IF( ln_zdftke.OR.ln_zdfgls ) THEN
462!      CALL Agrif_Set_Updatetype( en_id, update = AGRIF_Update_Full_Weighting)
463!      CALL Agrif_Set_Updatetype(avt_id, update = AGRIF_Update_Full_Weighting)
464!      CALL Agrif_Set_Updatetype(avm_id, update = AGRIF_Update_Full_Weighting)
465   ENDIF
466
467#else
468   CALL Agrif_Set_Updatetype(tsn_id, update = AGRIF_Update_Average)
469   CALL Agrif_Set_Updatetype(un_update_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average)
470   CALL Agrif_Set_Updatetype(vn_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy)
471
472   CALL Agrif_Set_Updatetype(ub2b_update_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average)
473   CALL Agrif_Set_Updatetype(vb2b_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy)
474   CALL Agrif_Set_Updatetype(sshn_id, update = AGRIF_Update_Average)
475   CALL Agrif_Set_Updatetype(e3t_id, update = AGRIF_Update_Average)
476
477   IF( ln_zdftke.OR.ln_zdfgls ) THEN
478!      CALL Agrif_Set_Updatetype( en_id, update = AGRIF_Update_Average)
479!      CALL Agrif_Set_Updatetype(avt_id, update = AGRIF_Update_Average)
480!      CALL Agrif_Set_Updatetype(avm_id, update = AGRIF_Update_Average)
481   ENDIF
482
483#endif
484   !
485END SUBROUTINE agrif_declare_var
486
487#if defined key_lim3
488SUBROUTINE Agrif_InitValues_cont_lim3
489   !!----------------------------------------------------------------------
490   !!                 *** ROUTINE Agrif_InitValues_cont_lim3 ***
491   !!
492   !! ** Purpose :: Initialisation of variables to be interpolated for LIM3
493   !!----------------------------------------------------------------------
494   USE Agrif_Util
495   USE sbc_oce, ONLY : nn_fsbc  ! clem: necessary otherwise Agrif_Parent(nn_fsbc) = nn_fsbc
496   USE ice
497   USE agrif_ice
498   USE in_out_manager
499   USE agrif_lim3_update
500   USE agrif_lim3_interp
501   USE lib_mpp
502   !
503   IMPLICIT NONE
504   !!----------------------------------------------------------------------
505   !
506   ! Declaration of the type of variable which have to be interpolated (parent=>child)
507   !----------------------------------------------------------------------------------
508   CALL agrif_declare_var_lim3
509
510   ! Controls
511
512   ! clem: For some reason, nn_fsbc(child)/=1 does not work properly (signal is largely degraded by the agrif zoom)
513   !          the run must satisfy CFL=Uice/(dx/dt) < 0.6/nn_fsbc(child)
514   !          therefore, if nn_fsbc(child)>1 one must reduce the time-step in proportion to nn_fsbc(child), which is not acceptable
515   !       If a solution is found, the following stop could be removed
516   IF( nn_fsbc > 1 )  CALL ctl_stop('nn_fsbc(child) must be set to 1 otherwise agrif and lim3 do not work properly')
517
518   ! stop if rhot * nn_fsbc(parent) /= N * nn_fsbc(child) with N being integer
519   IF( MOD( Agrif_irhot() * Agrif_Parent(nn_fsbc), nn_fsbc ) /= 0 )  THEN
520      CALL ctl_stop('rhot * nn_fsbc(parent) /= N * nn_fsbc(child), therefore nn_fsbc(child) should be set to 1 or nn_fsbc(parent)')
521   ENDIF
522   ! First Interpolations (using "after" ice subtime step => lim_nbstep=1)
523   !----------------------------------------------------------------------
524   lim_nbstep = ( Agrif_irhot() * Agrif_Parent(nn_fsbc) / nn_fsbc ) ! clem: to have calledweight=1 in interp (otherwise the western border of the zoom is wrong)
525   CALL agrif_interp_lim3('U') ! interpolation of ice velocities
526   CALL agrif_interp_lim3('V') ! interpolation of ice velocities
527   CALL agrif_interp_lim3('T') ! interpolation of ice tracers
528   lim_nbstep = 0
529   
530   ! Update in case 2 ways
531   !----------------------
532   CALL agrif_update_lim3(0)
533
534   !
535END SUBROUTINE Agrif_InitValues_cont_lim3
536
537SUBROUTINE agrif_declare_var_lim3
538   !!----------------------------------------------------------------------
539   !!                 *** ROUTINE agrif_declare_var_lim3 ***
540   !!
541   !! ** Purpose :: Declaration of variables to be interpolated for LIM3
542   !!----------------------------------------------------------------------
543   USE Agrif_Util
544   USE ice
545   USE par_oce, ONLY : nbghostcells
546   !
547   IMPLICIT NONE
548   !
549   INTEGER :: ind1, ind2, ind3
550   !!----------------------------------------------------------------------
551   !
552   ! 1. Declaration of the type of variable which have to be interpolated (parent=>child)
553   !       agrif_declare_variable(position,1st point index,--,--,dimensions,name)
554   !           ex.:  position=> 1,1 = not-centered (in i and j)
555   !                            2,2 =     centered (    -     )
556   !                 index   => 1,1 = one ghost line
557   !                            2,2 = two ghost lines
558   !-------------------------------------------------------------------------------------
559   ind1 =     nbghostcells
560   ind2 = 1 + nbghostcells
561   ind3 = 2 + nbghostcells
562   CALL agrif_declare_variable((/2,2,0/),(/ind3,ind3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpl*(8+nlay_s+nlay_i)/),tra_ice_id)
563   CALL agrif_declare_variable((/1,2/)  ,(/ind2,ind3/)  ,(/'x','y'/)    ,(/1,1/)  ,(/nlci,nlcj/)                      ,u_ice_id  )
564   CALL agrif_declare_variable((/2,1/)  ,(/ind3,ind2/)  ,(/'x','y'/)    ,(/1,1/)  ,(/nlci,nlcj/)                      ,v_ice_id  )
565
566   ! 2. Set interpolations (normal & tangent to the grid cell for velocities)
567   !-----------------------------------
568   CALL Agrif_Set_bcinterp(tra_ice_id, interp  = AGRIF_linear)
569   CALL Agrif_Set_bcinterp(u_ice_id  , interp1 = Agrif_linear,interp2 = AGRIF_ppm   )
570   CALL Agrif_Set_bcinterp(v_ice_id  , interp1 = AGRIF_ppm   ,interp2 = Agrif_linear)
571
572   ! 3. Set location of interpolations
573   !----------------------------------
574   CALL Agrif_Set_bc(tra_ice_id,(/0,ind1/))
575   CALL Agrif_Set_bc(u_ice_id  ,(/0,ind1/))
576   CALL Agrif_Set_bc(v_ice_id  ,(/0,ind1/))
577
578   ! 4. Set update type in case 2 ways (child=>parent) (normal & tangent to the grid cell for velocities)
579   !--------------------------------------------------
580# if defined UPD_HIGH
581   CALL Agrif_Set_Updatetype(tra_ice_id, update  = Agrif_Update_Full_Weighting)
582   CALL Agrif_Set_Updatetype(u_ice_id  , update1 = Agrif_Update_Average       , update2 = Agrif_Update_Full_Weighting)
583   CALL Agrif_Set_Updatetype(v_ice_id  , update1 = Agrif_Update_Full_Weighting, update2 = Agrif_Update_Average       )
584#else
585   CALL Agrif_Set_Updatetype(tra_ice_id, update  = AGRIF_Update_Average)
586   CALL Agrif_Set_Updatetype(u_ice_id  , update1 = Agrif_Update_Copy   , update2 = Agrif_Update_Average)
587   CALL Agrif_Set_Updatetype(v_ice_id  , update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy   )
588#endif
589
590END SUBROUTINE agrif_declare_var_lim3
591#endif
592
593
594# if defined key_top
595SUBROUTINE Agrif_InitValues_cont_top
596   !!----------------------------------------------------------------------
597   !!                 *** ROUTINE Agrif_InitValues_cont_top ***
598   !!
599   !! ** Purpose :: Declaration of variables to be interpolated
600   !!----------------------------------------------------------------------
601   USE Agrif_Util
602   USE oce 
603   USE dom_oce
604   USE nemogcm
605   USE par_trc
606   USE lib_mpp
607   USE trc
608   USE in_out_manager
609   USE agrif_opa_sponge
610   USE agrif_top_update
611   USE agrif_top_interp
612   USE agrif_top_sponge
613   !!
614   IMPLICIT NONE
615   !
616   CHARACTER(len=10) :: cl_check1, cl_check2, cl_check3
617   LOGICAL :: check_namelist
618   !!----------------------------------------------------------------------
619
620
621   ! 1. Declaration of the type of variable which have to be interpolated
622   !---------------------------------------------------------------------
623   CALL agrif_declare_var_top
624
625   ! 2. First interpolations of potentially non zero fields
626   !-------------------------------------------------------
627   Agrif_SpecialValue=0.
628   Agrif_UseSpecialValue = .TRUE.
629   CALL Agrif_Bc_variable(trn_id,calledweight=1.,procname=interptrn)
630   Agrif_UseSpecialValue = .FALSE.
631   CALL Agrif_Sponge
632   tabspongedone_trn = .FALSE.
633   CALL Agrif_Bc_variable(trn_sponge_id,calledweight=1.,procname=interptrn_sponge)
634   ! reset tsa to zero
635   tra(:,:,:,:) = 0.
636
637
638   ! 3. Some controls
639   !-----------------
640   check_namelist = .TRUE.
641
642   IF( check_namelist ) THEN
643      ! Check time steps
644      IF( NINT(Agrif_Rhot()) * NINT(rdt) .NE. Agrif_Parent(rdt) ) THEN
645         WRITE(cl_check1,*)  Agrif_Parent(rdt)
646         WRITE(cl_check2,*)  rdt
647         WRITE(cl_check3,*)  rdt*Agrif_Rhot()
648         CALL ctl_stop( 'incompatible time step between grids',   &
649               &               'parent grid value : '//cl_check1    ,   & 
650               &               'child  grid value : '//cl_check2    ,   & 
651               &               'value on child grid should be changed to  &
652               &               :'//cl_check3  )
653      ENDIF
654
655      ! Check run length
656      IF( Agrif_IRhot() * (Agrif_Parent(nitend)- &
657            Agrif_Parent(nit000)+1) .NE. (nitend-nit000+1) ) THEN
658         WRITE(cl_check1,*)  (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1
659         WRITE(cl_check2,*)   Agrif_Parent(nitend)   *Agrif_IRhot()
660         CALL ctl_warn( 'incompatible run length between grids'               ,   &
661               &              ' nit000 on fine grid will be change to : '//cl_check1,   &
662               &              ' nitend on fine grid will be change to : '//cl_check2    )
663         nit000 = (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1
664         nitend =  Agrif_Parent(nitend)   *Agrif_IRhot()
665      ENDIF
666
667      ENDIF
668      ! Check passive tracer cell
669      IF( nn_dttrc .NE. 1 ) THEN
670         WRITE(*,*) 'nn_dttrc should be equal to 1'
671      ENDIF
672   ENDIF
673   !
674END SUBROUTINE Agrif_InitValues_cont_top
675
676
677SUBROUTINE agrif_declare_var_top
678   !!----------------------------------------------------------------------
679   !!                 *** ROUTINE agrif_declare_var_top ***
680   !!
681   !! ** Purpose :: Declaration of TOP variables to be interpolated
682   !!----------------------------------------------------------------------
683   USE agrif_util
684   USE agrif_oce
685   USE dom_oce
686   USE trc
687   !!
688   IMPLICIT NONE
689   !
690   INTEGER :: ind1, ind2, ind3
691   !!----------------------------------------------------------------------
692
693   ! 1. Declaration of the type of variable which have to be interpolated
694   !---------------------------------------------------------------------
695   ind1 =     nbghostcells
696   ind2 = 1 + nbghostcells
697   ind3 = 2 + nbghostcells
698# if defined key_vertical
699   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jptra+1/),trn_id)
700   CALL agrif_declare_variable((/2,2,0,0/),(/ind3,ind3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jptra+1/),trn_sponge_id)
701# else
702   CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jptra/),trn_id)
703   CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/nlci,nlcj,jpk,jptra/),trn_sponge_id)
704# endif
705
706   ! 2. Type of interpolation
707   !-------------------------
708   CALL Agrif_Set_bcinterp(trn_id,interp=AGRIF_linear)
709   CALL Agrif_Set_bcinterp(trn_sponge_id,interp=AGRIF_linear)
710
711   ! 3. Location of interpolation
712   !-----------------------------
713   CALL Agrif_Set_bc(trn_id,(/0,ind1/))
714   CALL Agrif_Set_bc(trn_sponge_id,(/-nn_sponge_len*Agrif_irhox()-1,0/))
715
716   ! 4. Update type
717   !---------------
718# if defined UPD_HIGH
719   CALL Agrif_Set_Updatetype(trn_id, update = Agrif_Update_Full_Weighting)
720#else
721   CALL Agrif_Set_Updatetype(trn_id, update = AGRIF_Update_Average)
722#endif
723   !
724END SUBROUTINE agrif_declare_var_top
725# endif
726
727SUBROUTINE Agrif_detect( kg, ksizex )
728   !!----------------------------------------------------------------------
729   !!                      *** ROUTINE Agrif_detect ***
730   !!----------------------------------------------------------------------
731   INTEGER, DIMENSION(2) :: ksizex
732   INTEGER, DIMENSION(ksizex(1),ksizex(2)) :: kg 
733   !!----------------------------------------------------------------------
734   !
735   RETURN
736   !
737END SUBROUTINE Agrif_detect
738
739
740SUBROUTINE agrif_nemo_init
741   !!----------------------------------------------------------------------
742   !!                     *** ROUTINE agrif_init ***
743   !!----------------------------------------------------------------------
744   USE agrif_oce 
745   USE agrif_ice
746   USE in_out_manager
747   USE lib_mpp
748   !!
749   IMPLICIT NONE
750   !
751   INTEGER  ::   ios                 ! Local integer output status for namelist read
752   INTEGER  ::   iminspon
753   NAMELIST/namagrif/ rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn, ln_chk_bathy
754   !!--------------------------------------------------------------------------------------
755   !
756   REWIND( numnam_ref )              ! Namelist namagrif in reference namelist : AGRIF zoom
757   READ  ( numnam_ref, namagrif, IOSTAT = ios, ERR = 901)
758901 IF( ios /= 0 )   CALL ctl_nam ( ios , 'namagrif in reference namelist', lwp )
759   REWIND( numnam_cfg )              ! Namelist namagrif in configuration namelist : AGRIF zoom
760   READ  ( numnam_cfg, namagrif, IOSTAT = ios, ERR = 902 )
761902 IF( ios >  0 )   CALL ctl_nam ( ios , 'namagrif in configuration namelist', lwp )
762   IF(lwm) WRITE ( numond, namagrif )
763   !
764   IF(lwp) THEN                    ! control print
765      WRITE(numout,*)
766      WRITE(numout,*) 'agrif_nemo_init : AGRIF parameters'
767      WRITE(numout,*) '~~~~~~~~~~~~~~~'
768      WRITE(numout,*) '   Namelist namagrif : set AGRIF parameters'
769      WRITE(numout,*) '      sponge coefficient for tracers    rn_sponge_tra = ', rn_sponge_tra, ' s'
770      WRITE(numout,*) '      sponge coefficient for dynamics   rn_sponge_tra = ', rn_sponge_dyn, ' s'
771      WRITE(numout,*) '      use special values for dynamics   ln_spc_dyn    = ', ln_spc_dyn
772      WRITE(numout,*) '      check bathymetry                  ln_chk_bathy  = ', ln_chk_bathy
773   ENDIF
774   !
775   ! convert DOCTOR namelist name into OLD names
776   visc_tra      = rn_sponge_tra
777   visc_dyn      = rn_sponge_dyn
778   !
779   ! Check sponge length:
780   iminspon = MIN(FLOOR(REAL(jpiglo-4)/REAL(2*Agrif_irhox())), FLOOR(REAL(jpjglo-4)/REAL(2*Agrif_irhox())) )
781   IF (lk_mpp) iminspon = MIN(iminspon,FLOOR(REAL(jpi-2)/REAL(Agrif_irhox())), FLOOR(REAL(jpj-2)/REAL(Agrif_irhox())) )
782   IF (nn_sponge_len > iminspon)  CALL ctl_stop('agrif sponge length is too large')
783   !
784   IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif agrif_oce_alloc: allocation of arrays failed')
785   !
786END SUBROUTINE agrif_nemo_init
787
788# if defined key_mpp_mpi
789
790SUBROUTINE Agrif_InvLoc( indloc, nprocloc, i, indglob )
791   !!----------------------------------------------------------------------
792   !!                     *** ROUTINE Agrif_InvLoc ***
793   !!----------------------------------------------------------------------
794   USE dom_oce
795   !!
796   IMPLICIT NONE
797   !
798   INTEGER :: indglob, indloc, nprocloc, i
799   !!----------------------------------------------------------------------
800   !
801   SELECT CASE( i )
802   CASE(1)   ;   indglob = indloc + nimppt(nprocloc+1) - 1
803   CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1
804   CASE DEFAULT
805      indglob = indloc
806   END SELECT
807   !
808END SUBROUTINE Agrif_InvLoc
809
810
811SUBROUTINE Agrif_get_proc_info( imin, imax, jmin, jmax )
812   !!----------------------------------------------------------------------
813   !!                 *** ROUTINE Agrif_get_proc_info ***
814   !!----------------------------------------------------------------------
815   USE par_oce
816   !!
817   IMPLICIT NONE
818   !
819   INTEGER, INTENT(out) :: imin, imax
820   INTEGER, INTENT(out) :: jmin, jmax
821   !!----------------------------------------------------------------------
822   !
823   imin = nimppt(Agrif_Procrank+1)  ! ?????
824   jmin = njmppt(Agrif_Procrank+1)  ! ?????
825   imax = imin + jpi - 1
826   jmax = jmin + jpj - 1
827   !
828END SUBROUTINE Agrif_get_proc_info
829
830
831SUBROUTINE Agrif_estimate_parallel_cost(imin, imax,jmin, jmax, nbprocs, grid_cost)
832   !!----------------------------------------------------------------------
833   !!                 *** ROUTINE Agrif_estimate_parallel_cost ***
834   !!----------------------------------------------------------------------
835   USE par_oce
836   !!
837   IMPLICIT NONE
838   !
839   INTEGER,  INTENT(in)  :: imin, imax
840   INTEGER,  INTENT(in)  :: jmin, jmax
841   INTEGER,  INTENT(in)  :: nbprocs
842   REAL(wp), INTENT(out) :: grid_cost
843   !!----------------------------------------------------------------------
844   !
845   grid_cost = REAL(imax-imin+1,wp)*REAL(jmax-jmin+1,wp) / REAL(nbprocs,wp)
846   !
847END SUBROUTINE Agrif_estimate_parallel_cost
848
849# endif
850
851#else
852SUBROUTINE Subcalledbyagrif
853   !!----------------------------------------------------------------------
854   !!                   *** ROUTINE Subcalledbyagrif ***
855   !!----------------------------------------------------------------------
856   WRITE(*,*) 'Impossible to be here'
857END SUBROUTINE Subcalledbyagrif
858#endif
Note: See TracBrowser for help on using the repository browser.