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

source: branches/2017/dev_r8624_AGRIF3_VVL/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 @ 8965

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

Add ssh update at initialization, #1965

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