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

source: branches/2016/dev_merge_2016/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 @ 7421

Last change on this file since 7421 was 7421, checked in by flavoni, 7 years ago

#1811 merge dev_CNRS_MERATOR_2016 with dev_merge_2016 branch

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