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

source: branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 @ 7953

Last change on this file since 7953 was 7953, checked in by gm, 7 years ago

#1880 (HPC-09): add zdfphy (the ZDF manager) + remove all key_...

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