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.
Changeset 5656 for trunk/NEMOGCM/NEMO/NST_SRC/agrif_user.F90 – NEMO

Ignore:
Timestamp:
2015-07-31T10:55:56+02:00 (9 years ago)
Author:
timgraham
Message:

Merge of AGRIF branch (branches/2014/dev_r4765_CNRS_agrif) onto the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r5573 r5656  
    3030      jpi     = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci 
    3131      jpj     = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj 
    32       jpk     = jpkdta  
     32! JC: change to allow for different vertical levels 
     33!     jpk is already set 
     34!     keep it jpk possibly different from jpkdta which  
     35!     hold parent grid vertical levels number (set earlier) 
     36!      jpk     = jpkdta  
    3337      jpim1   = jpi-1  
    3438      jpjm1   = jpj-1  
     
    6367   ! 0. Initializations 
    6468   !------------------- 
    65    IF( cp_cfg == 'orca' ) then 
     69   IF( cp_cfg == 'orca' ) THEN 
    6670      IF ( jp_cfg == 2 .OR. jp_cfg == 025 .OR. jp_cfg == 05 & 
    67   &                      .OR. jp_cfg == 4 ) THEN 
     71            &                      .OR. jp_cfg == 4 ) THEN 
    6872         jp_cfg = -1    ! set special value for jp_cfg on fine grids 
    6973         cp_cfg = "default" 
     
    119123SUBROUTINE agrif_declare_var_dom 
    120124   !!---------------------------------------------------------------------- 
    121    !!                 *** ROUTINE agrif_declarE_var *** 
     125   !!                 *** ROUTINE agrif_declare_var *** 
    122126   !! 
    123127   !! ** Purpose :: Declaration of variables to be interpolated 
    124128   !!---------------------------------------------------------------------- 
    125129   USE agrif_util 
    126    USE par_oce       !   ONLY : jpts 
     130   USE par_oce        
    127131   USE oce 
    128132   IMPLICIT NONE 
     
    131135   ! 1. Declaration of the type of variable which have to be interpolated 
    132136   !--------------------------------------------------------------------- 
    133    CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e1u_id) 
    134    CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e2v_id) 
    135  
     137   CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),e1u_id) 
     138   CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),e2v_id) 
    136139 
    137140   ! 2. Type of interpolation 
    138141   !------------------------- 
    139    Call Agrif_Set_bcinterp(e1u_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    140    Call Agrif_Set_bcinterp(e2v_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     142   CALL Agrif_Set_bcinterp(e1u_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     143   CALL Agrif_Set_bcinterp(e2v_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    141144 
    142145   ! 3. Location of interpolation 
    143146   !----------------------------- 
    144    Call Agrif_Set_bc(e1u_id,(/0,0/)) 
    145    Call Agrif_Set_bc(e2v_id,(/0,0/)) 
     147   CALL Agrif_Set_bc(e1u_id,(/0,0/)) 
     148   CALL Agrif_Set_bc(e2v_id,(/0,0/)) 
    146149 
    147150   ! 5. Update type 
    148151   !---------------  
    149    Call Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average) 
    150    Call Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy) 
    151  
     152   CALL Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average) 
     153   CALL Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy) 
     154 
     155! High order updates 
     156!   CALL Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Average,            update2=Agrif_Update_Full_Weighting) 
     157!   CALL Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Full_Weighting,     update2=Agrif_Update_Average) 
     158    ! 
    152159END SUBROUTINE agrif_declare_var_dom 
    153160 
     
    166173   USE nemogcm 
    167174   USE sol_oce 
     175   USE lib_mpp 
    168176   USE in_out_manager 
    169177   USE agrif_opa_update 
     
    173181   IMPLICIT NONE 
    174182   ! 
    175    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtstemp 
    176    REAL(wp), DIMENSION(:,:,:  ), ALLOCATABLE :: tabuvtemp 
    177    REAL(wp), DIMENSION(:,:    ), ALLOCATABLE :: tab2d 
    178183   LOGICAL :: check_namelist 
    179    !!---------------------------------------------------------------------- 
    180  
    181    ALLOCATE( tabtstemp(jpi, jpj, jpk, jpts) ) 
    182    ALLOCATE( tabuvtemp(jpi, jpj, jpk)       ) 
    183    ALLOCATE( tab2d(jpi, jpj)                ) 
    184  
     184   CHARACTER(len=15) :: cl_check1, cl_check2, cl_check3 
     185   !!---------------------------------------------------------------------- 
    185186 
    186187   ! 1. Declaration of the type of variable which have to be interpolated 
     
    192193   Agrif_SpecialValue=0. 
    193194   Agrif_UseSpecialValue = .TRUE. 
    194    Call Agrif_Bc_variable(tabtstemp,tsn_id,calledweight=1.,procname=interptsn) 
    195    Call Agrif_Bc_variable(tabtstemp,tsa_id,calledweight=1.,procname=interptsn) 
    196  
    197    Call Agrif_Bc_variable(tabuvtemp,un_id,calledweight=1.,procname=interpu) 
    198    Call Agrif_Bc_variable(tabuvtemp,vn_id,calledweight=1.,procname=interpv) 
    199    Call Agrif_Bc_variable(tabuvtemp,ua_id,calledweight=1.,procname=interpun) 
    200    Call Agrif_Bc_variable(tabuvtemp,va_id,calledweight=1.,procname=interpvn) 
    201  
    202    Call Agrif_Bc_variable(tab2d,unb_id,calledweight=1.,procname=interpunb) 
    203    Call Agrif_Bc_variable(tab2d,vnb_id,calledweight=1.,procname=interpvnb) 
    204    Call Agrif_Bc_variable(tab2d,sshn_id,calledweight=1.,procname=interpsshn) 
    205    Agrif_UseSpecialValue = .FALSE. 
     195   CALL Agrif_Bc_variable(tsn_id,calledweight=1.,procname=interptsn) 
     196   CALL Agrif_Sponge 
     197   tabspongedone_tsn = .FALSE. 
     198   CALL Agrif_Bc_variable(tsn_sponge_id,calledweight=1.,procname=interptsn_sponge) 
     199   ! reset tsa to zero 
     200   tsa(:,:,:,:) = 0. 
     201 
     202   Agrif_UseSpecialValue = ln_spc_dyn 
     203   CALL Agrif_Bc_variable(un_interp_id,calledweight=1.,procname=interpun) 
     204   CALL Agrif_Bc_variable(vn_interp_id,calledweight=1.,procname=interpvn) 
     205   tabspongedone_u = .FALSE. 
     206   tabspongedone_v = .FALSE. 
     207   CALL Agrif_Bc_variable(un_sponge_id,calledweight=1.,procname=interpun_sponge) 
     208   tabspongedone_u = .FALSE. 
     209   tabspongedone_v = .FALSE. 
     210   CALL Agrif_Bc_variable(vn_sponge_id,calledweight=1.,procname=interpvn_sponge) 
     211 
     212#if defined key_dynspg_ts 
     213   Agrif_UseSpecialValue = .TRUE. 
     214   CALL Agrif_Bc_variable(sshn_id,calledweight=1., procname=interpsshn ) 
     215 
     216   Agrif_UseSpecialValue = ln_spc_dyn 
     217   CALL Agrif_Bc_variable(unb_id,calledweight=1.,procname=interpunb) 
     218   CALL Agrif_Bc_variable(vnb_id,calledweight=1.,procname=interpvnb) 
     219   CALL Agrif_Bc_variable(ub2b_interp_id,calledweight=1.,procname=interpub2b) 
     220   CALL Agrif_Bc_variable(vb2b_interp_id,calledweight=1.,procname=interpvb2b) 
     221   ubdy_w(:) = 0.e0 ; vbdy_w(:) = 0.e0 ; hbdy_w(:) =0.e0 
     222   ubdy_e(:) = 0.e0 ; vbdy_e(:) = 0.e0 ; hbdy_e(:) =0.e0  
     223   ubdy_n(:) = 0.e0 ; vbdy_n(:) = 0.e0 ; hbdy_n(:) =0.e0  
     224   ubdy_s(:) = 0.e0 ; vbdy_s(:) = 0.e0 ; hbdy_s(:) =0.e0 
     225#endif 
     226 
     227   Agrif_UseSpecialValue = .FALSE.  
     228   ! reset velocities to zero 
     229   ua(:,:,:) = 0. 
     230   va(:,:,:) = 0. 
    206231 
    207232   ! 3. Some controls 
    208233   !----------------- 
    209    check_namelist = .true. 
    210  
    211    IF( check_namelist ) THEN 
     234   check_namelist = .TRUE. 
     235 
     236   IF( check_namelist ) THEN  
    212237 
    213238      ! Check time steps            
    214       IF( NINT(Agrif_Rhot()) * nint(rdt) /= Agrif_Parent(rdt) ) THEN 
    215          WRITE(*,*) 'incompatible time step between grids' 
    216          WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt) 
    217          WRITE(*,*) 'child  grid value : ',nint(rdt) 
    218          WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot() 
    219          STOP 
     239      IF( NINT(Agrif_Rhot()) * NINT(rdt) .NE. Agrif_Parent(rdt) ) THEN 
     240         WRITE(cl_check1,*)  NINT(Agrif_Parent(rdt)) 
     241         WRITE(cl_check2,*)  NINT(rdt) 
     242         WRITE(cl_check3,*)  NINT(Agrif_Parent(rdt)/Agrif_Rhot()) 
     243         CALL ctl_warn( 'incompatible time step between grids',   & 
     244               &               'parent grid value : '//cl_check1    ,   &  
     245               &               'child  grid value : '//cl_check2    ,   &  
     246               &               'value on child grid will be changed to : '//cl_check3 ) 
     247         rdt=Agrif_Parent(rdt)/Agrif_Rhot() 
    220248      ENDIF 
    221249 
    222250      ! Check run length 
    223251      IF( Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    224            Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN 
    225          WRITE(*,*) 'incompatible run length between grids' 
    226          WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- & 
    227               Agrif_Parent(nit000)+1),' time step' 
    228          WRITE(*,*) 'child  grid value : ', & 
    229               (nitend-nit000+1),' time step' 
    230          WRITE(*,*) 'value on child grid should be : ', & 
    231               Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    232               Agrif_Parent(nit000)+1) 
    233          STOP 
     252            Agrif_Parent(nit000)+1) .NE. (nitend-nit000+1) ) THEN 
     253         WRITE(cl_check1,*)  (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1 
     254         WRITE(cl_check2,*)   Agrif_Parent(nitend)   *Agrif_IRhot() 
     255         CALL ctl_warn( 'incompatible run length between grids'               ,   & 
     256               &              ' nit000 on fine grid will be change to : '//cl_check1,   & 
     257               &              ' nitend on fine grid will be change to : '//cl_check2    ) 
     258         nit000 = (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1 
     259         nitend =  Agrif_Parent(nitend)   *Agrif_IRhot() 
    234260      ENDIF 
    235261 
     
    237263      IF( ln_zps ) THEN 
    238264         ! check parameters for partial steps  
    239          IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN 
     265         IF( Agrif_Parent(e3zps_min) .NE. e3zps_min ) THEN 
    240266            WRITE(*,*) 'incompatible e3zps_min between grids' 
    241267            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
     
    252278         ENDIF 
    253279      ENDIF 
     280      ! check if masks and bathymetries match 
     281      IF(ln_chk_bathy) THEN 
     282         ! 
     283         IF(lwp) WRITE(numout,*) 'AGRIF: Check Bathymetry and masks near bdys. Level: ', Agrif_Level() 
     284         ! 
     285         kindic_agr = 0 
     286         ! check if umask agree with parent along western and eastern boundaries: 
     287         CALL Agrif_Bc_variable(umsk_id,calledweight=1.,procname=interpumsk) 
     288         ! check if vmask agree with parent along northern and southern boundaries: 
     289         CALL Agrif_Bc_variable(vmsk_id,calledweight=1.,procname=interpvmsk) 
     290    ! check if tmask and vertical scale factors agree with parent over first two coarse grid points: 
     291         CALL Agrif_Bc_variable(e3t_id,calledweight=1.,procname=interpe3t) 
     292         ! 
     293         IF (lk_mpp) CALL mpp_sum( kindic_agr ) 
     294         IF( kindic_agr /= 0 ) THEN                    
     295            CALL ctl_stop('Child Bathymetry is not correct near boundaries.') 
     296         ELSE 
     297            IF(lwp) WRITE(numout,*) 'Child Bathymetry is ok near boundaries.' 
     298         END IF 
     299      ENDIF 
     300      ! 
    254301   ENDIF 
    255  
    256    CALL Agrif_Update_tra(0) 
    257    CALL Agrif_Update_dyn(0) 
    258  
     302   !  
     303   ! Do update at initialisation because not done before writing restarts 
     304   ! This would indeed change boundary conditions values at initial time 
     305   ! hence produce restartability issues. 
     306   ! Note that update below is recursive (with lk_agrif_doupd=T): 
     307   !  
     308! JC: I am not sure if Agrif_MaxLevel() is the "relative" 
     309!     or the absolute maximum nesting level...TBC                         
     310   IF ( Agrif_Level().EQ.Agrif_MaxLevel() ) THEN  
     311      ! NB: Do tracers first, dynamics after because nbcline incremented in dynamics 
     312      CALL Agrif_Update_tra() 
     313      CALL Agrif_Update_dyn() 
     314   ENDIF 
     315   ! 
     316# if defined key_zdftke 
     317   CALL Agrif_Update_tke(0) 
     318# endif 
     319   ! 
     320   Agrif_UseSpecialValueInUpdate = .FALSE. 
    259321   nbcline = 0 
    260    ! 
    261    DEALLOCATE(tabtstemp) 
    262    DEALLOCATE(tabuvtemp) 
    263    DEALLOCATE(tab2d) 
     322   lk_agrif_doupd = .FALSE. 
    264323   ! 
    265324END SUBROUTINE Agrif_InitValues_cont 
     
    275334   USE par_oce       !   ONLY : jpts 
    276335   USE oce 
     336   USE agrif_oce 
    277337   IMPLICIT NONE 
    278338   !!---------------------------------------------------------------------- 
     
    280340   ! 1. Declaration of the type of variable which have to be interpolated 
    281341   !--------------------------------------------------------------------- 
    282    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jpts/),tsn_id) 
    283    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jpts/),tsa_id) 
    284    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jpts/),tsb_id) 
    285  
    286    CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),un_id) 
    287    CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),vn_id) 
    288    CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),ua_id) 
    289    CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),va_id) 
    290  
    291    CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),unb_id) 
    292    CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),vnb_id) 
    293    CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),sshn_id) 
    294    CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),gcb_id) 
    295    CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),ub2b_id) 
    296    CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),vb2b_id) 
     342   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) 
     343   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) 
     344 
     345   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),un_interp_id) 
     346   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vn_interp_id) 
     347   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),un_update_id) 
     348   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vn_update_id) 
     349   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),un_sponge_id) 
     350   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vn_sponge_id) 
     351 
     352   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),e3t_id) 
     353   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),umsk_id) 
     354   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpk/),vmsk_id) 
     355 
     356   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) 
     357 
     358   CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),unb_id) 
     359   CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),vnb_id) 
     360   CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),ub2b_interp_id) 
     361   CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),vb2b_interp_id) 
     362   CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),ub2b_update_id) 
     363   CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),vb2b_update_id) 
     364 
     365   CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/nlci,nlcj/),sshn_id) 
     366 
     367# if defined key_zdftke 
     368   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/), en_id) 
     369   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),avt_id) 
     370   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),avm_id) 
     371# endif 
    297372 
    298373   ! 2. Type of interpolation 
    299374   !------------------------- 
    300375   CALL Agrif_Set_bcinterp(tsn_id,interp=AGRIF_linear) 
    301    CALL Agrif_Set_bcinterp(tsa_id,interp=AGRIF_linear) 
    302  
    303    Call Agrif_Set_bcinterp(un_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    304    Call Agrif_Set_bcinterp(vn_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    305  
    306    Call Agrif_Set_bcinterp(ua_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    307    Call Agrif_Set_bcinterp(va_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     376 
     377   CALL Agrif_Set_bcinterp(un_interp_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     378   CALL Agrif_Set_bcinterp(vn_interp_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     379 
     380   CALL Agrif_Set_bcinterp(tsn_sponge_id,interp=AGRIF_linear) 
    308381 
    309382   CALL Agrif_Set_bcinterp(sshn_id,interp=AGRIF_linear) 
    310    Call Agrif_Set_bcinterp(unb_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    311    Call Agrif_Set_bcinterp(vnb_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    312    Call Agrif_Set_bcinterp(ub2b_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    313    Call Agrif_Set_bcinterp(vb2b_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     383   CALL Agrif_Set_bcinterp(unb_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     384   CALL Agrif_Set_bcinterp(vnb_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     385   CALL Agrif_Set_bcinterp(ub2b_interp_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     386   CALL Agrif_Set_bcinterp(vb2b_interp_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     387 
     388 
     389   CALL Agrif_Set_bcinterp(un_sponge_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     390   CALL Agrif_Set_bcinterp(vn_sponge_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     391 
     392   CALL Agrif_Set_bcinterp(e3t_id,interp=AGRIF_constant) 
     393   CALL Agrif_Set_bcinterp(umsk_id,interp=AGRIF_constant) 
     394   CALL Agrif_Set_bcinterp(vmsk_id,interp=AGRIF_constant) 
     395 
     396# if defined key_zdftke 
     397   CALL Agrif_Set_bcinterp(avm_id ,interp=AGRIF_linear) 
     398# endif 
     399 
    314400 
    315401   ! 3. Location of interpolation 
    316402   !----------------------------- 
    317    Call Agrif_Set_bc(un_id,(/0,1/)) 
    318    Call Agrif_Set_bc(vn_id,(/0,1/)) 
    319  
    320    Call Agrif_Set_bc(sshn_id,(/0,1/)) 
    321    Call Agrif_Set_bc(unb_id,(/0,1/)) 
    322    Call Agrif_Set_bc(vnb_id,(/0,1/)) 
    323    Call Agrif_Set_bc(ub2b_id,(/0,1/)) 
    324    Call Agrif_Set_bc(vb2b_id,(/0,1/)) 
    325  
    326    Call Agrif_Set_bc(tsn_id,(/0,1/)) 
    327    Call Agrif_Set_bc(tsa_id,(/-3*Agrif_irhox(),0/)) 
    328  
    329    Call Agrif_Set_bc(ua_id,(/-2*Agrif_irhox(),0/)) 
    330    Call Agrif_Set_bc(va_id,(/-2*Agrif_irhox(),0/)) 
     403   CALL Agrif_Set_bc(tsn_id,(/0,1/)) 
     404   CALL Agrif_Set_bc(un_interp_id,(/0,1/)) 
     405   CALL Agrif_Set_bc(vn_interp_id,(/0,1/)) 
     406 
     407!   CALL Agrif_Set_bc(tsn_sponge_id,(/-3*Agrif_irhox(),0/)) 
     408!   CALL Agrif_Set_bc(un_sponge_id,(/-2*Agrif_irhox()-1,0/)) 
     409!   CALL Agrif_Set_bc(vn_sponge_id,(/-2*Agrif_irhox()-1,0/)) 
     410   CALL Agrif_Set_bc(tsn_sponge_id,(/-nn_sponge_len*Agrif_irhox()-1,0/)) 
     411   CALL Agrif_Set_bc(un_sponge_id ,(/-nn_sponge_len*Agrif_irhox()-1,0/)) 
     412   CALL Agrif_Set_bc(vn_sponge_id ,(/-nn_sponge_len*Agrif_irhox()-1,0/)) 
     413 
     414   CALL Agrif_Set_bc(sshn_id,(/0,0/)) 
     415   CALL Agrif_Set_bc(unb_id ,(/0,0/)) 
     416   CALL Agrif_Set_bc(vnb_id ,(/0,0/)) 
     417   CALL Agrif_Set_bc(ub2b_interp_id,(/0,0/)) 
     418   CALL Agrif_Set_bc(vb2b_interp_id,(/0,0/)) 
     419 
     420   CALL Agrif_Set_bc(e3t_id,(/-2*Agrif_irhox()-1,0/))   ! if west and rhox=3: column 2 to 9 
     421   CALL Agrif_Set_bc(umsk_id,(/0,0/)) 
     422   CALL Agrif_Set_bc(vmsk_id,(/0,0/)) 
     423 
     424# if defined key_zdftke 
     425   CALL Agrif_Set_bc(avm_id ,(/0,1/)) 
     426# endif 
    331427 
    332428   ! 5. Update type 
    333429   !---------------  
    334    Call Agrif_Set_Updatetype(tsn_id, update = AGRIF_Update_Average) 
    335    Call Agrif_Set_Updatetype(tsb_id, update = AGRIF_Update_Average) 
    336  
    337    Call Agrif_Set_Updatetype(sshn_id, update = AGRIF_Update_Average) 
    338    Call Agrif_Set_Updatetype(gcb_id,update = AGRIF_Update_Average) 
    339  
    340    Call Agrif_Set_Updatetype(un_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
    341    Call Agrif_Set_Updatetype(vn_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
    342  
    343    Call Agrif_Set_Updatetype(ub2b_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
    344    Call Agrif_Set_Updatetype(vb2b_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
    345  
     430   CALL Agrif_Set_Updatetype(tsn_id, update = AGRIF_Update_Average) 
     431 
     432   CALL Agrif_Set_Updatetype(scales_t_id, update = AGRIF_Update_Average) 
     433 
     434   CALL Agrif_Set_Updatetype(un_update_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     435   CALL Agrif_Set_Updatetype(vn_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     436 
     437   CALL Agrif_Set_Updatetype(sshn_id, update = AGRIF_Update_Average) 
     438 
     439   CALL Agrif_Set_Updatetype(ub2b_update_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     440   CALL Agrif_Set_Updatetype(vb2b_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     441 
     442# if defined key_zdftke 
     443   CALL Agrif_Set_Updatetype( en_id, update = AGRIF_Update_Average) 
     444   CALL Agrif_Set_Updatetype(avt_id, update = AGRIF_Update_Average) 
     445   CALL Agrif_Set_Updatetype(avm_id, update = AGRIF_Update_Average) 
     446# endif 
     447 
     448! High order updates 
     449!   CALL Agrif_Set_Updatetype(tsn_id, update = Agrif_Update_Full_Weighting) 
     450!   CALL Agrif_Set_Updatetype(un_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Full_Weighting) 
     451!   CALL Agrif_Set_Updatetype(vn_update_id,update1 = Agrif_Update_Full_Weighting, update2 = Agrif_Update_Average) 
     452! 
     453!   CALL Agrif_Set_Updatetype(ub2b_update_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Full_Weighting) 
     454!   CALL Agrif_Set_Updatetype(vb2b_update_id,update1 = Agrif_Update_Full_Weighting, update2 = Agrif_Update_Average) 
     455!   CALL Agrif_Set_Updatetype(sshn_id, update = Agrif_Update_Full_Weighting) 
     456  
     457   ! 
    346458END SUBROUTINE agrif_declare_var 
    347459# endif 
     
    364476   IMPLICIT NONE 
    365477   ! 
    366    REAL(wp), DIMENSION(:,:)  , ALLOCATABLE :: zvel 
    367    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zadv 
    368    !!---------------------------------------------------------------------- 
    369  
    370    ALLOCATE( zvel(jpi,jpj), zadv(jpi,jpj,7)) 
     478   !!---------------------------------------------------------------------- 
    371479 
    372480   ! 1. Declaration of the type of variable which have to be interpolated 
     
    400508   CALL Agrif_Update_lim2(0) 
    401509   ! 
    402    DEALLOCATE( zvel, zadv ) 
    403    ! 
    404510END SUBROUTINE Agrif_InitValues_cont_lim2 
    405511 
     
    430536   !------------------------- 
    431537   CALL Agrif_Set_bcinterp(adv_ice_id ,interp=AGRIF_linear) 
    432    Call Agrif_Set_bcinterp(u_ice_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    433    Call Agrif_Set_bcinterp(v_ice_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     538   CALL Agrif_Set_bcinterp(u_ice_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     539   CALL Agrif_Set_bcinterp(v_ice_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    434540 
    435541   ! 3. Location of interpolation 
    436542   !----------------------------- 
    437    Call Agrif_Set_bc(adv_ice_id ,(/0,1/)) 
    438    Call Agrif_Set_bc(u_ice_id,(/0,1/)) 
    439    Call Agrif_Set_bc(v_ice_id,(/0,1/)) 
     543   CALL Agrif_Set_bc(adv_ice_id ,(/0,1/)) 
     544   CALL Agrif_Set_bc(u_ice_id,(/0,1/)) 
     545   CALL Agrif_Set_bc(v_ice_id,(/0,1/)) 
    440546 
    441547   ! 5. Update type 
    442548   !--------------- 
    443    Call Agrif_Set_Updatetype(adv_ice_id , update = AGRIF_Update_Average) 
    444    Call Agrif_Set_Updatetype(u_ice_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
    445    Call Agrif_Set_Updatetype(v_ice_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
    446  
     549   CALL Agrif_Set_Updatetype(adv_ice_id , update = AGRIF_Update_Average) 
     550   CALL Agrif_Set_Updatetype(u_ice_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     551   CALL Agrif_Set_Updatetype(v_ice_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     552   !  
    447553END SUBROUTINE agrif_declare_var_lim2 
    448554#  endif 
     
    461567   USE nemogcm 
    462568   USE par_trc 
     569   USE lib_mpp 
    463570   USE trc 
    464571   USE in_out_manager 
     572   USE agrif_opa_sponge 
    465573   USE agrif_top_update 
    466574   USE agrif_top_interp 
     
    469577   IMPLICIT NONE 
    470578   ! 
    471    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtrtemp 
     579   CHARACTER(len=10) :: cl_check1, cl_check2, cl_check3 
    472580   LOGICAL :: check_namelist 
    473581   !!---------------------------------------------------------------------- 
    474  
    475    ALLOCATE( tabtrtemp(jpi,jpj,jpk,jptra) ) 
    476582 
    477583 
     
    484590   Agrif_SpecialValue=0. 
    485591   Agrif_UseSpecialValue = .TRUE. 
    486    Call Agrif_Bc_variable(tabtrtemp,trn_id,calledweight=1.,procname=interptrn) 
    487    Call Agrif_Bc_variable(tabtrtemp,tra_id,calledweight=1.,procname=interptrn) 
     592   CALL Agrif_Bc_variable(trn_id,calledweight=1.,procname=interptrn) 
    488593   Agrif_UseSpecialValue = .FALSE. 
     594   CALL Agrif_Sponge 
     595   tabspongedone_trn = .FALSE. 
     596   CALL Agrif_Bc_variable(trn_sponge_id,calledweight=1.,procname=interptrn_sponge) 
     597   ! reset tsa to zero 
     598   tra(:,:,:,:) = 0. 
     599 
    489600 
    490601   ! 3. Some controls 
    491602   !----------------- 
    492    check_namelist = .true. 
     603   check_namelist = .TRUE. 
    493604 
    494605   IF( check_namelist ) THEN 
    495 #  if defined offline      
     606# if defined key_offline 
    496607      ! Check time steps 
    497       IF( nint(Agrif_Rhot()) * nint(rdt) .ne. Agrif_Parent(rdt) ) THEN 
    498          WRITE(*,*) 'incompatible time step between grids' 
    499          WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt) 
    500          WRITE(*,*) 'child  grid value : ',nint(rdt) 
    501          WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot() 
    502          STOP 
     608      IF( NINT(Agrif_Rhot()) * NINT(rdt) .NE. Agrif_Parent(rdt) ) THEN 
     609         WRITE(cl_check1,*)  Agrif_Parent(rdt) 
     610         WRITE(cl_check2,*)  rdt 
     611         WRITE(cl_check3,*)  rdt*Agrif_Rhot() 
     612         CALL ctl_warn( 'incompatible time step between grids',   & 
     613               &               'parent grid value : '//cl_check1    ,   &  
     614               &               'child  grid value : '//cl_check2    ,   &  
     615               &               'value on child grid will be changed to  & 
     616               &               :'//cl_check3  ) 
     617         rdt=rdt*Agrif_Rhot() 
    503618      ENDIF 
    504619 
    505620      ! Check run length 
    506621      IF( Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    507            Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN 
    508          WRITE(*,*) 'incompatible run length between grids' 
    509          WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- & 
    510               Agrif_Parent(nit000)+1),' time step' 
    511          WRITE(*,*) 'child  grid value : ', & 
    512               (nitend-nit000+1),' time step' 
    513          WRITE(*,*) 'value on child grid should be : ', & 
    514               Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    515               Agrif_Parent(nit000)+1) 
    516          STOP 
     622            Agrif_Parent(nit000)+1) .NE. (nitend-nit000+1) ) THEN 
     623         WRITE(cl_check1,*)  (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1 
     624         WRITE(cl_check2,*)   Agrif_Parent(nitend)   *Agrif_IRhot() 
     625         CALL ctl_warn( 'incompatible run length between grids'               ,   & 
     626               &              ' nit000 on fine grid will be change to : '//cl_check1,   & 
     627               &              ' nitend on fine grid will be change to : '//cl_check2    ) 
     628         nit000 = (Agrif_Parent(nit000)-1)*Agrif_IRhot() + 1 
     629         nitend =  Agrif_Parent(nitend)   *Agrif_IRhot() 
    517630      ENDIF 
    518631 
     
    520633      IF( ln_zps ) THEN 
    521634         ! check parameters for partial steps  
    522          IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN 
     635         IF( Agrif_Parent(e3zps_min) .NE. e3zps_min ) THEN 
    523636            WRITE(*,*) 'incompatible e3zps_min between grids' 
    524637            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
     
    527640            STOP 
    528641         ENDIF 
    529          IF( Agrif_Parent(e3zps_rat) .ne. e3zps_rat ) THEN 
     642         IF( Agrif_Parent(e3zps_rat) .NE. e3zps_rat ) THEN 
    530643            WRITE(*,*) 'incompatible e3zps_rat between grids' 
    531644            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
     
    537650#  endif          
    538651      ! Check passive tracer cell 
    539       IF( nn_dttrc .ne. 1 ) THEN 
     652      IF( nn_dttrc .NE. 1 ) THEN 
    540653         WRITE(*,*) 'nn_dttrc should be equal to 1' 
    541654      ENDIF 
    542655   ENDIF 
    543656 
    544 !ch   CALL Agrif_Update_trc(0) 
     657   CALL Agrif_Update_trc(0) 
     658   ! 
     659   Agrif_UseSpecialValueInUpdate = .FALSE. 
    545660   nbcline_trc = 0 
    546    ! 
    547    DEALLOCATE(tabtrtemp) 
    548661   ! 
    549662END SUBROUTINE Agrif_InitValues_cont_top 
     
    557670   !!---------------------------------------------------------------------- 
    558671   USE agrif_util 
     672   USE agrif_oce 
    559673   USE dom_oce 
    560674   USE trc 
     
    564678   ! 1. Declaration of the type of variable which have to be interpolated 
    565679   !--------------------------------------------------------------------- 
    566    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jptra/),trn_id) 
    567    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jptra/),trb_id) 
    568    CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/),(/jpi,jpj,jpk,jptra/),tra_id) 
     680   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) 
     681   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) 
    569682 
    570683   ! 2. Type of interpolation 
    571684   !------------------------- 
    572685   CALL Agrif_Set_bcinterp(trn_id,interp=AGRIF_linear) 
    573    CALL Agrif_Set_bcinterp(tra_id,interp=AGRIF_linear) 
     686   CALL Agrif_Set_bcinterp(trn_sponge_id,interp=AGRIF_linear) 
    574687 
    575688   ! 3. Location of interpolation 
    576689   !----------------------------- 
    577    Call Agrif_Set_bc(trn_id,(/0,1/)) 
    578    Call Agrif_Set_bc(tra_id,(/-3*Agrif_irhox(),0/)) 
     690   CALL Agrif_Set_bc(trn_id,(/0,1/)) 
     691!   CALL Agrif_Set_bc(trn_sponge_id,(/-3*Agrif_irhox(),0/)) 
     692   CALL Agrif_Set_bc(trn_sponge_id,(/-nn_sponge_len*Agrif_irhox()-1,0/)) 
    579693 
    580694   ! 5. Update type 
    581695   !---------------  
    582    Call Agrif_Set_Updatetype(trn_id, update = AGRIF_Update_Average) 
    583    Call Agrif_Set_Updatetype(trb_id, update = AGRIF_Update_Average) 
    584  
    585  
     696   CALL Agrif_Set_Updatetype(trn_id, update = AGRIF_Update_Average) 
     697 
     698!   Higher order update 
     699!   CALL Agrif_Set_Updatetype(tsn_id, update = Agrif_Update_Full_Weighting) 
     700 
     701   ! 
    586702END SUBROUTINE agrif_declare_var_top 
    587703# endif 
     
    591707   !!   *** ROUTINE Agrif_detect *** 
    592708   !!---------------------------------------------------------------------- 
    593    USE Agrif_Types 
    594709   ! 
    595710   INTEGER, DIMENSION(2) :: ksizex 
     
    613728   ! 
    614729   INTEGER  ::   ios                 ! Local integer output status for namelist read 
    615    NAMELIST/namagrif/ nn_cln_update, rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn 
    616    !!---------------------------------------------------------------------- 
    617    ! 
    618       REWIND( numnam_ref )              ! Namelist namagrif in reference namelist : AGRIF zoom 
    619       READ  ( numnam_ref, namagrif, IOSTAT = ios, ERR = 901) 
    620 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namagrif in reference namelist', lwp ) 
    621  
    622       REWIND( numnam_cfg )              ! Namelist namagrif in configuration namelist : AGRIF zoom 
    623       READ  ( numnam_cfg, namagrif, IOSTAT = ios, ERR = 902 ) 
    624 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namagrif in configuration namelist', lwp ) 
    625       IF(lwm) WRITE ( numond, namagrif ) 
     730   INTEGER  ::   iminspon 
     731   NAMELIST/namagrif/ nn_cln_update, rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn, ln_chk_bathy 
     732   !!-------------------------------------------------------------------------------------- 
     733   ! 
     734   REWIND( numnam_ref )              ! Namelist namagrif in reference namelist : AGRIF zoom 
     735   READ  ( numnam_ref, namagrif, IOSTAT = ios, ERR = 901) 
     736901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namagrif in reference namelist', lwp ) 
     737 
     738   REWIND( numnam_cfg )              ! Namelist namagrif in configuration namelist : AGRIF zoom 
     739   READ  ( numnam_cfg, namagrif, IOSTAT = ios, ERR = 902 ) 
     740902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namagrif in configuration namelist', lwp ) 
     741   IF(lwm) WRITE ( numond, namagrif ) 
    626742   ! 
    627743   IF(lwp) THEN                    ! control print 
     
    634750      WRITE(numout,*) '      sponge coefficient for dynamics   rn_sponge_tra = ', rn_sponge_dyn, ' s' 
    635751      WRITE(numout,*) '      use special values for dynamics   ln_spc_dyn    = ', ln_spc_dyn 
     752      WRITE(numout,*) '      check bathymetry                  ln_chk_bathy  = ', ln_chk_bathy 
    636753      WRITE(numout,*)  
    637754   ENDIF 
     
    642759   visc_dyn      = rn_sponge_dyn 
    643760   ! 
    644    IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif sol_oce_alloc: allocation of arrays failed') 
     761   ! Check sponge length: 
     762   iminspon = MIN(FLOOR(REAL(jpiglo-4)/REAL(2*Agrif_irhox())), FLOOR(REAL(jpjglo-4)/REAL(2*Agrif_irhox())) ) 
     763   IF (lk_mpp) iminspon = MIN(iminspon,FLOOR(REAL(jpi-2)/REAL(Agrif_irhox())), FLOOR(REAL(jpj-2)/REAL(Agrif_irhox())) ) 
     764   IF (nn_sponge_len > iminspon)  CALL ctl_stop('agrif sponge length is too large') 
     765   ! 
     766   IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif agrif_oce_alloc: allocation of arrays failed') 
    645767# if defined key_lim2 
    646768   IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') 
     
    663785   SELECT CASE( i ) 
    664786   CASE(1)   ;   indglob = indloc + nimppt(nprocloc+1) - 1 
    665    CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1  
    666    CASE(3)   ;   indglob = indloc 
    667    CASE(4)   ;   indglob = indloc 
     787   CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1 
     788   CASE DEFAULT 
     789      indglob = indloc 
    668790   END SELECT 
    669791   ! 
    670792END SUBROUTINE Agrif_InvLoc 
     793 
     794SUBROUTINE Agrif_get_proc_info( imin, imax, jmin, jmax ) 
     795   !!---------------------------------------------------------------------- 
     796   !!                 *** ROUTINE Agrif_get_proc_info *** 
     797   !!---------------------------------------------------------------------- 
     798   USE par_oce 
     799   IMPLICIT NONE 
     800   ! 
     801   INTEGER, INTENT(out) :: imin, imax 
     802   INTEGER, INTENT(out) :: jmin, jmax 
     803   !!---------------------------------------------------------------------- 
     804   ! 
     805   imin = nimppt(Agrif_Procrank+1)  ! ????? 
     806   jmin = njmppt(Agrif_Procrank+1)  ! ????? 
     807   imax = imin + jpi - 1 
     808   jmax = jmin + jpj - 1 
     809   !  
     810END SUBROUTINE Agrif_get_proc_info 
     811 
     812SUBROUTINE Agrif_estimate_parallel_cost(imin, imax,jmin, jmax, nbprocs, grid_cost) 
     813   !!---------------------------------------------------------------------- 
     814   !!                 *** ROUTINE Agrif_estimate_parallel_cost *** 
     815   !!---------------------------------------------------------------------- 
     816   USE par_oce 
     817   IMPLICIT NONE 
     818   ! 
     819   INTEGER,  INTENT(in)  :: imin, imax 
     820   INTEGER,  INTENT(in)  :: jmin, jmax 
     821   INTEGER,  INTENT(in)  :: nbprocs 
     822   REAL(wp), INTENT(out) :: grid_cost 
     823   !!---------------------------------------------------------------------- 
     824   ! 
     825   grid_cost = REAL(imax-imin+1,wp)*REAL(jmax-jmin+1,wp) / REAL(nbprocs,wp) 
     826   ! 
     827END SUBROUTINE Agrif_estimate_parallel_cost 
    671828 
    672829# endif 
Note: See TracChangeset for help on using the changeset viewer.