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 @ 7485

Last change on this file since 7485 was 7485, checked in by cetlod, 7 years ago

Remove CPP key key_offline and replace it with a logical l_offline

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