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 NEMO/trunk/src/NST – NEMO

source: NEMO/trunk/src/NST/agrif_user.F90 @ 9748

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

Make online bathymetry check compliant with nesting tools

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