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

source: trunk/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 @ 7761

Last change on this file since 7761 was 7761, checked in by clem, 7 years ago

make AGRIF and LIM3 fully compatible

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