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 3454 for branches – NEMO

Changeset 3454 for branches


Ignore:
Timestamp:
2012-08-21T10:01:18+02:00 (12 years ago)
Author:
rblod
Message:

branch dev_r3387_LOCEAN6_AGRIF_LIM: add modified routines, see ticket #848

Location:
branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/LIM_SRC_2/limrhg_2.F90

    r3294 r3454  
    3030   USE in_out_manager ! I/O manager 
    3131   USE prtctl         ! Print control 
     32#if defined key_agrif 
     33   USE agrif_lim2_interp ! nesting 
     34#endif 
    3235 
    3336   IMPLICIT NONE 
     
    129132!i    zviszeta(:,jpj+1) = 0._wp    ;    zviseta(:,jpj+1) = 0._wp 
    130133 
     134#if defined key_agrif 
     135      ! load the boundary value of velocity in special array zuive and zvice 
     136      CALL agrif_rhg_lim2_load 
     137#endif 
    131138 
    132139      ! Ice mass, ice strength, and wind stress at the center            | 
     
    533540            CALL lbc_lnk( zv_n(:,1:jpj), 'I', -1. ) 
    534541 
     542#if defined key_agrif 
     543            ! copy the boundary value from u_ice_nst and v_ice_nst to u_ice and v_ice 
     544            ! before next interations 
     545            CALL agrif_rhg_lim2(zu_n,zv_n) 
     546#endif 
     547 
    535548            ! Test of Convergence 
    536549            DO jj = k_j1+1 , k_jpj-1 
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/LIM_SRC_2/limtrp_2.F90

    r3294 r3454  
    2828   USE lib_mpp         ! MPP library 
    2929   USE wrk_nemo        ! work arrays 
     30# if defined key_agrif 
     31   USE agrif_lim2_interp ! nesting 
     32# endif 
    3033 
    3134   IMPLICIT NONE 
     
    8083 
    8184      IF( kt == nit000  )   CALL lim_trp_init_2      ! Initialization (first time-step only) 
     85 
     86# if defined key_agrif 
     87      CALL agrif_trp_lim2_load      ! First interpolation 
     88# endif 
    8289 
    8390      zsm(:,:) = area(:,:) 
     
    269276      ENDIF 
    270277      ! 
     278# if defined key_agrif 
     279      CALL agrif_trp_lim2      ! Fill boundaries of the fine grid 
     280# endif 
     281      !  
    271282      CALL wrk_dealloc( jpi, jpj, zui_u , zvi_v , zsm, zs0ice, zs0sn , zs0a, zs0c0 , zs0c1 , zs0c2 , zs0st ) 
    272283      ! 
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r3294 r3454  
    88   !!             -   !  2008-11  (M. Vancoppenolle, S. Bouillon, Y. Aksenov) add surface tilt in ice rheolohy  
    99   !!            3.3  !  2009-05  (G.Garric) addition of the lim2_evp cas 
    10    !!            4.0  !  2011-01  (A Porter)  dynamical allocation  
     10   !!            3.4  !  2011-01  (A. Porter)  dynamical allocation  
     11   !!            3.5  !  2012-08  (R. Benshila)  AGRIF  
    1112   !!---------------------------------------------------------------------- 
    1213#if defined key_lim3 || (  defined key_lim2 && ! defined key_lim2_vp ) 
     
    3435   USE ice_2            ! LIM2: ice variables 
    3536   USE dom_ice_2        ! LIM2: ice domain 
     37#endif 
     38#if defined key_agrif && defined key_lim2 
     39   USE agrif_lim2_interp 
    3640#endif 
    3741 
     
    162166     at_i(:,:) = 1. - frld(:,:) 
    163167#endif 
     168#if defined key_agrif && defined key_lim2  
     169    CALL agrif_rhg_lim2_load      ! First interpolation of coarse values 
     170#endif 
    164171      ! 
    165172      !------------------------------------------------------------------------------! 
     
    488495 
    489496            CALL lbc_lnk( u_ice(:,:), 'U', -1. ) 
     497#if defined key_agrif 
     498            CALL agrif_rhg_lim2( jter, nevp, 'U' ) 
     499#endif 
    490500 
    491501!CDIR NOVERRCHK 
     
    513523 
    514524            CALL lbc_lnk( v_ice(:,:), 'V', -1. ) 
     525#if defined key_agrif 
     526            CALL agrif_rhg_lim2( jter, nevp, 'V' ) 
     527#endif 
    515528 
    516529         ELSE  
     
    539552 
    540553            CALL lbc_lnk( v_ice(:,:), 'V', -1. ) 
     554#if defined key_agrif 
     555            CALL agrif_rhg_lim2( jter, nevp , 'V' ) 
     556#endif 
    541557 
    542558!CDIR NOVERRCHK 
     
    567583 
    568584            CALL lbc_lnk( u_ice(:,:), 'U', -1. ) 
     585#if defined key_agrif 
     586            CALL agrif_rhg_lim2( jter, nevp, 'U' ) 
     587#endif 
    569588 
    570589         ENDIF 
     
    607626      CALL lbc_lnk( u_ice(:,:), 'U', -1. )  
    608627      CALL lbc_lnk( v_ice(:,:), 'V', -1. )  
     628#if defined key_agrif 
     629      CALL agrif_rhg_lim2( nevp , nevp, 'U' ) 
     630      CALL agrif_rhg_lim2( nevp , nevp, 'V' ) 
     631#endif 
    609632 
    610633      DO jj = k_j1+1, k_jpj-1  
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/NST_SRC/agrif_oce.F90

    r3294 r3454  
    2525 
    2626   !                                              !!! OLD namelist names 
     27   INTEGER , PUBLIC ::   nbcline = 0               !: update counter 
    2728   INTEGER , PUBLIC ::   nbclineupdate             !: update frequency  
    2829   REAL(wp), PUBLIC ::   visc_tra                  !: sponge coeff. for tracers 
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r3390 r3454  
    11#if defined key_agrif 
    2    !!---------------------------------------------------------------------- 
    3    !! NEMO/NST 3.3 , NEMO Consortium (2010) 
    4    !! $Id$ 
    5    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    6    !!---------------------------------------------------------------------- 
    7    SUBROUTINE agrif_user 
    8    END SUBROUTINE 
    9  
    10    SUBROUTINE agrif_before_regridding 
    11    END SUBROUTINE 
    12  
    13    SUBROUTINE Agrif_InitWorkspace 
    14       !!---------------------------------------------------------------------- 
    15       !!                 *** ROUTINE Agrif_InitWorkspace *** 
    16       !!---------------------------------------------------------------------- 
    17       USE par_oce 
    18       USE dom_oce 
    19       USE Agrif_Util 
    20       USE nemogcm 
    21       ! 
    22       IMPLICIT NONE 
    23       !!---------------------------------------------------------------------- 
    24       ! 
    25       IF( .NOT. Agrif_Root() ) THEN 
    26          jpni = Agrif_Parent(jpni) 
    27          jpnj = Agrif_Parent(jpnj) 
    28          jpnij = Agrif_Parent(jpnij) 
    29          jpiglo  = nbcellsx + 2 + 2*nbghostcells 
    30          jpjglo  = nbcellsy + 2 + 2*nbghostcells 
    31          jpi     = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci 
    32          jpj     = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj 
    33          jpk     = jpkdta 
    34          jpim1   = jpi-1 
    35          jpjm1   = jpj-1 
    36          jpkm1   = jpk-1                                         
    37          jpij    = jpi*jpj 
    38          jpidta  = jpiglo 
    39          jpjdta  = jpjglo 
    40          jpizoom = 1 
    41          jpjzoom = 1 
    42          nperio  = 0 
    43          jperio  = 0 
    44       ENDIF 
    45       ! 
    46    END SUBROUTINE Agrif_InitWorkspace 
    47  
    48  
    49    SUBROUTINE Agrif_InitValues 
    50       !!---------------------------------------------------------------------- 
    51       !!                 *** ROUTINE Agrif_InitValues *** 
    52       !! 
    53       !! ** Purpose :: Declaration of variables to be interpolated 
    54       !!---------------------------------------------------------------------- 
    55       USE Agrif_Util 
    56       USE oce  
    57       USE dom_oce 
    58       USE nemogcm 
    59       USE tradmp 
    60       USE obc_par 
    61       USE bdy_par 
    62  
    63       IMPLICIT NONE 
    64       !!---------------------------------------------------------------------- 
    65  
    66       ! 0. Initializations 
    67       !------------------- 
     2!!---------------------------------------------------------------------- 
     3!! NEMO/NST 3.4 , NEMO Consortium (2012) 
     4!! $Id$ 
     5!! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     6!!---------------------------------------------------------------------- 
     7SUBROUTINE agrif_user 
     8END SUBROUTINE agrif_user 
     9 
     10SUBROUTINE agrif_before_regridding 
     11END SUBROUTINE agrif_before_regridding 
     12 
     13SUBROUTINE Agrif_InitWorkspace 
     14   !!---------------------------------------------------------------------- 
     15   !!                 *** ROUTINE Agrif_InitWorkspace *** 
     16   !!---------------------------------------------------------------------- 
     17   USE par_oce 
     18   USE dom_oce 
     19   USE Agrif_Util 
     20   USE nemogcm 
     21   ! 
     22   IMPLICIT NONE 
     23   !!---------------------------------------------------------------------- 
     24   ! 
     25   IF( .NOT. Agrif_Root() ) THEN 
     26      jpni = Agrif_Parent(jpni) 
     27      jpnj = Agrif_Parent(jpnj) 
     28      jpnij = Agrif_Parent(jpnij) 
     29      jpiglo  = nbcellsx + 2 + 2*nbghostcells 
     30      jpjglo  = nbcellsy + 2 + 2*nbghostcells 
     31      jpi     = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci 
     32      jpj     = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj 
     33      jpk     = jpkdta 
     34      jpim1   = jpi-1 
     35      jpjm1   = jpj-1 
     36      jpkm1   = jpk-1                                         
     37      jpij    = jpi*jpj 
     38      jpidta  = jpiglo 
     39      jpjdta  = jpjglo 
     40      jpizoom = 1 
     41      jpjzoom = 1 
     42      nperio  = 0 
     43      jperio  = 0 
     44   ENDIF 
     45   ! 
     46END SUBROUTINE Agrif_InitWorkspace 
     47 
     48 
     49SUBROUTINE Agrif_InitValues 
     50   !!---------------------------------------------------------------------- 
     51   !!                 *** ROUTINE Agrif_InitValues *** 
     52   !! 
     53   !! ** Purpose :: Declaration of variables to be interpolated 
     54   !!---------------------------------------------------------------------- 
     55   USE Agrif_Util 
     56   USE oce  
     57   USE dom_oce 
     58   USE nemogcm 
     59   USE tradmp 
     60   USE obc_par 
     61   USE bdy_par 
     62 
     63   IMPLICIT NONE 
     64   !!---------------------------------------------------------------------- 
     65 
     66   ! 0. Initializations 
     67   !------------------- 
    6868#if defined key_orca_r025 || defined key_orca_r05 || defined key_orca_r2 || defined key_orca_r4 
    69       jp_cfg = -1    ! set special value for jp_cfg on fine grids 
    70       cp_cfg = "default" 
     69   jp_cfg = -1    ! set special value for jp_cfg on fine grids 
     70   cp_cfg = "default" 
    7171#endif 
    7272 
    73       ! Specific fine grid Initializations 
    74       ! no tracer damping on fine grids 
    75       ln_tradmp = .FALSE. 
    76       ! no open boundary on fine grids 
    77       lk_obc = .FALSE. 
    78       lk_bdy = .FALSE. 
    79  
    80       CALL nemo_init  ! Initializations of each fine grid 
    81       CALL agrif_nemo_init 
     73   ! Specific fine grid Initializations 
     74   ! no tracer damping on fine grids 
     75   ln_tradmp = .FALSE. 
     76   ! no open boundary on fine grids 
     77   lk_obc = .FALSE. 
     78   lk_bdy = .FALSE. 
     79 
     80   CALL nemo_init  ! Initializations of each fine grid 
     81   CALL agrif_nemo_init 
     82   CALL Agrif_InitValues_cont_dom 
    8283# if ! defined key_offline 
    83       CALL Agrif_InitValues_cont 
     84   CALL Agrif_InitValues_cont 
    8485# endif        
    8586# if defined key_top 
    86       CALL Agrif_InitValues_cont_top 
     87   CALL Agrif_InitValues_cont_top 
    8788# endif       
    88    END SUBROUTINE Agrif_initvalues 
     89END SUBROUTINE Agrif_initvalues 
     90 
     91 
     92SUBROUTINE Agrif_InitValues_cont_dom 
     93   !!---------------------------------------------------------------------- 
     94   !!                 *** ROUTINE Agrif_InitValues_cont *** 
     95   !! 
     96   !! ** Purpose ::   Declaration of variables to be interpolated 
     97   !!---------------------------------------------------------------------- 
     98   USE Agrif_Util 
     99   USE oce  
     100   USE dom_oce 
     101   USE nemogcm 
     102   USE sol_oce 
     103   USE in_out_manager 
     104   USE agrif_opa_update 
     105   USE agrif_opa_interp 
     106   USE agrif_opa_sponge 
     107   ! 
     108   IMPLICIT NONE 
     109   ! 
     110   !!---------------------------------------------------------------------- 
     111 
     112   ! Declaration of the type of variable which have to be interpolated 
     113   !--------------------------------------------------------------------- 
     114   CALL agrif_declare_var_dom 
     115   ! 
     116END SUBROUTINE Agrif_InitValues_cont_dom 
     117 
     118 
     119SUBROUTINE agrif_declare_var_dom 
     120   !!---------------------------------------------------------------------- 
     121   !!                 *** ROUTINE agrif_declarE_var *** 
     122   !! 
     123   !! ** Purpose :: Declaration of variables to be interpolated 
     124   !!---------------------------------------------------------------------- 
     125   USE agrif_util 
     126   USE par_oce       !   ONLY : jpts 
     127   USE oce 
     128   IMPLICIT NONE 
     129   !!---------------------------------------------------------------------- 
     130 
     131   ! 1. Declaration of the type of variable which have to be interpolated 
     132   !--------------------------------------------------------------------- 
     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 
     136 
     137   ! 2. Type of interpolation 
     138   !------------------------- 
     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) 
     141 
     142   ! 3. Location of interpolation 
     143   !----------------------------- 
     144   Call Agrif_Set_bc(e1u_id,(/0,0/)) 
     145   Call Agrif_Set_bc(e2v_id,(/0,0/)) 
     146 
     147   ! 5. Update type 
     148   !---------------  
     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 
     152END SUBROUTINE agrif_declare_var_dom 
     153 
    89154 
    90155# if ! defined key_offline 
    91156 
    92    SUBROUTINE Agrif_InitValues_cont 
    93       !!---------------------------------------------------------------------- 
    94       !!                 *** ROUTINE Agrif_InitValues_cont *** 
    95       !! 
    96       !! ** Purpose ::   Declaration of variables to be interpolated 
    97       !!---------------------------------------------------------------------- 
    98       USE Agrif_Util 
    99       USE oce  
    100       USE dom_oce 
    101       USE nemogcm 
    102       USE sol_oce 
    103       USE in_out_manager 
    104       USE agrif_opa_update 
    105       USE agrif_opa_interp 
    106       USE agrif_opa_sponge 
    107       ! 
    108       IMPLICIT NONE 
    109       ! 
    110       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtstemp 
    111       REAL(wp), DIMENSION(:,:,:  ), ALLOCATABLE :: tabuvtemp 
    112       LOGICAL :: check_namelist 
    113       !!---------------------------------------------------------------------- 
    114  
    115       ALLOCATE( tabtstemp(jpi, jpj, jpk, jpts) ) 
    116       ALLOCATE( tabuvtemp(jpi, jpj, jpk)       ) 
    117  
    118  
    119       ! 1. Declaration of the type of variable which have to be interpolated 
    120       !--------------------------------------------------------------------- 
    121       CALL agrif_declare_var 
    122  
    123       ! 2. First interpolations of potentially non zero fields 
    124       !------------------------------------------------------- 
    125       Agrif_SpecialValue=0. 
    126       Agrif_UseSpecialValue = .TRUE. 
    127       Call Agrif_Bc_variable(tabtstemp,tsn_id,calledweight=1.,procname=interptsn) 
    128       Call Agrif_Bc_variable(tabtstemp,tsa_id,calledweight=1.,procname=interptsn) 
    129  
    130       Call Agrif_Bc_variable(tabuvtemp,un_id,calledweight=1.,procname=interpu) 
    131       Call Agrif_Bc_variable(tabuvtemp,vn_id,calledweight=1.,procname=interpv) 
    132       Call Agrif_Bc_variable(tabuvtemp,ua_id,calledweight=1.,procname=interpun) 
    133       Call Agrif_Bc_variable(tabuvtemp,va_id,calledweight=1.,procname=interpvn) 
    134       Agrif_UseSpecialValue = .FALSE. 
    135  
    136       ! 3. Some controls 
    137       !----------------- 
    138       check_namelist = .true. 
    139              
    140       IF( check_namelist ) THEN 
    141       
    142          ! Check time steps            
    143          IF( NINT(Agrif_Rhot()) * nint(rdt) /= Agrif_Parent(rdt) ) THEN 
    144             WRITE(*,*) 'incompatible time step between grids' 
    145             WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt) 
    146             WRITE(*,*) 'child  grid value : ',nint(rdt) 
    147             WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot() 
     157SUBROUTINE Agrif_InitValues_cont 
     158   !!---------------------------------------------------------------------- 
     159   !!                 *** ROUTINE Agrif_InitValues_cont *** 
     160   !! 
     161   !! ** Purpose ::   Declaration of variables to be interpolated 
     162   !!---------------------------------------------------------------------- 
     163   USE Agrif_Util 
     164   USE oce  
     165   USE dom_oce 
     166   USE nemogcm 
     167   USE sol_oce 
     168   USE in_out_manager 
     169   USE agrif_opa_update 
     170   USE agrif_opa_interp 
     171   USE agrif_opa_sponge 
     172   ! 
     173   IMPLICIT NONE 
     174   ! 
     175   REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtstemp 
     176   REAL(wp), DIMENSION(:,:,:  ), ALLOCATABLE :: tabuvtemp 
     177   LOGICAL :: check_namelist 
     178   !!---------------------------------------------------------------------- 
     179 
     180   ALLOCATE( tabtstemp(jpi, jpj, jpk, jpts) ) 
     181   ALLOCATE( tabuvtemp(jpi, jpj, jpk)       ) 
     182 
     183 
     184   ! 1. Declaration of the type of variable which have to be interpolated 
     185   !--------------------------------------------------------------------- 
     186   CALL agrif_declare_var 
     187 
     188   ! 2. First interpolations of potentially non zero fields 
     189   !------------------------------------------------------- 
     190   Agrif_SpecialValue=0. 
     191   Agrif_UseSpecialValue = .TRUE. 
     192   Call Agrif_Bc_variable(tabtstemp,tsn_id,calledweight=1.,procname=interptsn) 
     193   Call Agrif_Bc_variable(tabtstemp,tsa_id,calledweight=1.,procname=interptsn) 
     194 
     195   Call Agrif_Bc_variable(tabuvtemp,un_id,calledweight=1.,procname=interpu) 
     196   Call Agrif_Bc_variable(tabuvtemp,vn_id,calledweight=1.,procname=interpv) 
     197   Call Agrif_Bc_variable(tabuvtemp,ua_id,calledweight=1.,procname=interpun) 
     198   Call Agrif_Bc_variable(tabuvtemp,va_id,calledweight=1.,procname=interpvn) 
     199   Agrif_UseSpecialValue = .FALSE. 
     200 
     201   ! 3. Some controls 
     202   !----------------- 
     203   check_namelist = .true. 
     204 
     205   IF( check_namelist ) THEN 
     206 
     207      ! Check time steps            
     208      IF( NINT(Agrif_Rhot()) * nint(rdt) /= Agrif_Parent(rdt) ) THEN 
     209         WRITE(*,*) 'incompatible time step between grids' 
     210         WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt) 
     211         WRITE(*,*) 'child  grid value : ',nint(rdt) 
     212         WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot() 
     213         STOP 
     214      ENDIF 
     215 
     216      ! Check run length 
     217      IF( Agrif_IRhot() * (Agrif_Parent(nitend)- & 
     218           Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN 
     219         WRITE(*,*) 'incompatible run length between grids' 
     220         WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- & 
     221              Agrif_Parent(nit000)+1),' time step' 
     222         WRITE(*,*) 'child  grid value : ', & 
     223              (nitend-nit000+1),' time step' 
     224         WRITE(*,*) 'value on child grid should be : ', & 
     225              Agrif_IRhot() * (Agrif_Parent(nitend)- & 
     226              Agrif_Parent(nit000)+1) 
     227         STOP 
     228      ENDIF 
     229 
     230      ! Check coordinates 
     231      IF( ln_zps ) THEN 
     232         ! check parameters for partial steps  
     233         IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN 
     234            WRITE(*,*) 'incompatible e3zps_min between grids' 
     235            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
     236            WRITE(*,*) 'child grid  :',e3zps_min 
     237            WRITE(*,*) 'those values should be identical' 
    148238            STOP 
    149239         ENDIF 
    150           
    151          ! Check run length 
    152          IF( Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    153             Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN 
    154             WRITE(*,*) 'incompatible run length between grids' 
    155             WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- & 
    156                Agrif_Parent(nit000)+1),' time step' 
    157             WRITE(*,*) 'child  grid value : ', & 
    158                (nitend-nit000+1),' time step' 
    159             WRITE(*,*) 'value on child grid should be : ', & 
    160                Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    161                Agrif_Parent(nit000)+1) 
     240         IF( Agrif_Parent(e3zps_rat) /= e3zps_rat ) THEN 
     241            WRITE(*,*) 'incompatible e3zps_rat between grids' 
     242            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
     243            WRITE(*,*) 'child grid  :',e3zps_rat 
     244            WRITE(*,*) 'those values should be identical'                   
    162245            STOP 
    163246         ENDIF 
    164           
    165          ! Check coordinates 
    166          IF( ln_zps ) THEN 
    167             ! check parameters for partial steps  
    168             IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN 
    169                WRITE(*,*) 'incompatible e3zps_min between grids' 
    170                WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
    171                WRITE(*,*) 'child grid  :',e3zps_min 
    172                WRITE(*,*) 'those values should be identical' 
    173                STOP 
    174             ENDIF           
    175             IF( Agrif_Parent(e3zps_rat) /= e3zps_rat ) THEN 
    176                WRITE(*,*) 'incompatible e3zps_rat between grids' 
    177                WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
    178                WRITE(*,*) 'child grid  :',e3zps_rat 
    179                WRITE(*,*) 'those values should be identical'                   
    180                STOP 
    181             ENDIF 
     247      ENDIF 
     248   ENDIF 
     249 
     250   CALL Agrif_Update_tra(0) 
     251   CALL Agrif_Update_dyn(0) 
     252 
     253   nbcline = 0 
     254   ! 
     255   DEALLOCATE(tabtstemp) 
     256   DEALLOCATE(tabuvtemp) 
     257   ! 
     258END SUBROUTINE Agrif_InitValues_cont 
     259 
     260 
     261SUBROUTINE agrif_declare_var 
     262   !!---------------------------------------------------------------------- 
     263   !!                 *** ROUTINE agrif_declarE_var *** 
     264   !! 
     265   !! ** Purpose :: Declaration of variables to be interpolated 
     266   !!---------------------------------------------------------------------- 
     267   USE agrif_util 
     268   USE par_oce       !   ONLY : jpts 
     269   USE oce 
     270   IMPLICIT NONE 
     271   !!---------------------------------------------------------------------- 
     272 
     273   ! 1. Declaration of the type of variable which have to be interpolated 
     274   !--------------------------------------------------------------------- 
     275   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) 
     276   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) 
     277   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) 
     278 
     279   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),un_id) 
     280   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),vn_id) 
     281   CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),ua_id) 
     282   CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),va_id) 
     283 
     284   CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),sshn_id) 
     285   CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),gcb_id) 
     286 
     287   ! 2. Type of interpolation 
     288   !------------------------- 
     289   CALL Agrif_Set_bcinterp(tsn_id,interp=AGRIF_linear) 
     290   CALL Agrif_Set_bcinterp(tsa_id,interp=AGRIF_linear) 
     291 
     292   Call Agrif_Set_bcinterp(un_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     293   Call Agrif_Set_bcinterp(vn_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     294 
     295   Call Agrif_Set_bcinterp(ua_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     296   Call Agrif_Set_bcinterp(va_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     297 
     298   ! 3. Location of interpolation 
     299   !----------------------------- 
     300   Call Agrif_Set_bc(un_id,(/0,1/)) 
     301   Call Agrif_Set_bc(vn_id,(/0,1/)) 
     302 
     303   Call Agrif_Set_bc(tsn_id,(/0,1/)) 
     304   Call Agrif_Set_bc(tsa_id,(/-3*Agrif_irhox(),0/)) 
     305 
     306   Call Agrif_Set_bc(ua_id,(/-2*Agrif_irhox(),0/)) 
     307   Call Agrif_Set_bc(va_id,(/-2*Agrif_irhox(),0/)) 
     308 
     309   ! 5. Update type 
     310   !---------------  
     311   Call Agrif_Set_Updatetype(tsn_id, update = AGRIF_Update_Average) 
     312   Call Agrif_Set_Updatetype(tsb_id, update = AGRIF_Update_Average) 
     313 
     314   Call Agrif_Set_Updatetype(sshn_id, update = AGRIF_Update_Average) 
     315   Call Agrif_Set_Updatetype(gcb_id,update = AGRIF_Update_Average) 
     316 
     317   Call Agrif_Set_Updatetype(un_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     318   Call Agrif_Set_Updatetype(vn_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     319 
     320END SUBROUTINE agrif_declare_var 
     321# endif 
     322 
     323#  if defined key_lim2 
     324SUBROUTINE Agrif_InitValues_cont_lim2 
     325   !!---------------------------------------------------------------------- 
     326   !!                 *** ROUTINE Agrif_InitValues_cont_lim2 *** 
     327   !! 
     328   !! ** Purpose :: Initialisation of variables to be interpolated for LIM2 
     329   !!---------------------------------------------------------------------- 
     330   USE Agrif_Util 
     331   USE ice_2 
     332   USE agrif_ice 
     333   USE in_out_manager 
     334   USE agrif_lim2_update 
     335   USE agrif_lim2_interp 
     336   USE lib_mpp 
     337   ! 
     338   IMPLICIT NONE 
     339   ! 
     340   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE :: zvel 
     341   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zadv 
     342   !!---------------------------------------------------------------------- 
     343 
     344   ALLOCATE( zvel(jpi,jpj), zadv(jpi,jpj,7)) 
     345 
     346   ! 1. Declaration of the type of variable which have to be interpolated 
     347   !--------------------------------------------------------------------- 
     348   CALL agrif_declare_var_lim2 
     349 
     350   ! 2. First interpolations of potentially non zero fields 
     351   !------------------------------------------------------- 
     352   Agrif_SpecialValue=-9999. 
     353   Agrif_UseSpecialValue = .TRUE. 
     354   !     Call Agrif_Bc_variable(zadv ,adv_ice_id ,calledweight=1.,procname=interp_adv_ice ) 
     355   !     Call Agrif_Bc_variable(zvel ,u_ice_id   ,calledweight=1.,procname=interp_u_ice   ) 
     356   !     Call Agrif_Bc_variable(zvel ,v_ice_id   ,calledweight=1.,procname=interp_v_ice   ) 
     357   Agrif_SpecialValue=0. 
     358   Agrif_UseSpecialValue = .FALSE. 
     359 
     360   ! 3. Some controls 
     361   !----------------- 
     362 
     363#   if ! defined key_lim2_vp 
     364   lim_nbstep = 1. 
     365   CALL agrif_rhg_lim2_load 
     366   CALL agrif_trp_lim2_load 
     367   lim_nbstep = 0. 
     368#   endif 
     369   !RB mandatory but why ??? 
     370   !      IF( nbclineupdate /= nn_fsbc .AND. nn_ice == 2 )THEN 
     371   !         CALL ctl_warn ('With ice model on child grid, nbclineupdate is set to nn_fsbc') 
     372   !         nbclineupdate = nn_fsbc 
     373   !       ENDIF 
     374   CALL Agrif_Update_lim2(0) 
     375   ! 
     376   DEALLOCATE( zvel, zadv ) 
     377   ! 
     378END SUBROUTINE Agrif_InitValues_cont_lim2 
     379 
     380SUBROUTINE agrif_declare_var_lim2 
     381   !!---------------------------------------------------------------------- 
     382   !!                 *** ROUTINE agrif_declare_var_lim2 *** 
     383   !! 
     384   !! ** Purpose :: Declaration of variables to be interpolated for LIM2 
     385   !!---------------------------------------------------------------------- 
     386   USE agrif_util 
     387   USE ice_2 
     388 
     389   IMPLICIT NONE 
     390   !!---------------------------------------------------------------------- 
     391 
     392   ! 1. Declaration of the type of variable which have to be interpolated 
     393   !--------------------------------------------------------------------- 
     394   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj, 7/),adv_ice_id ) 
     395#   if defined key_lim2_vp 
     396   CALL agrif_declare_variable((/1,1/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),u_ice_id) 
     397   CALL agrif_declare_variable((/1,1/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),v_ice_id) 
     398#   else 
     399   CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),u_ice_id) 
     400   CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),v_ice_id) 
     401#   endif 
     402 
     403   ! 2. Type of interpolation 
     404   !------------------------- 
     405   CALL Agrif_Set_bcinterp(adv_ice_id ,interp=AGRIF_linear) 
     406   Call Agrif_Set_bcinterp(u_ice_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     407   Call Agrif_Set_bcinterp(v_ice_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     408 
     409   ! 3. Location of interpolation 
     410   !----------------------------- 
     411   Call Agrif_Set_bc(adv_ice_id ,(/0,1/)) 
     412   Call Agrif_Set_bc(u_ice_id,(/0,1/)) 
     413   Call Agrif_Set_bc(v_ice_id,(/0,1/)) 
     414 
     415   ! 5. Update type 
     416   !--------------- 
     417   Call Agrif_Set_Updatetype(adv_ice_id , update = AGRIF_Update_Average) 
     418   Call Agrif_Set_Updatetype(u_ice_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     419   Call Agrif_Set_Updatetype(v_ice_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     420 
     421END SUBROUTINE agrif_declare_var_lim2 
     422#  endif 
     423 
     424 
     425# if defined key_top 
     426SUBROUTINE Agrif_InitValues_cont_top 
     427   !!---------------------------------------------------------------------- 
     428   !!                 *** ROUTINE Agrif_InitValues_cont_top *** 
     429   !! 
     430   !! ** Purpose :: Declaration of variables to be interpolated 
     431   !!---------------------------------------------------------------------- 
     432   USE Agrif_Util 
     433   USE oce  
     434   USE dom_oce 
     435   USE nemogcm 
     436   USE trc 
     437   USE in_out_manager 
     438   USE agrif_top_update 
     439   USE agrif_top_interp 
     440   USE agrif_top_sponge 
     441   ! 
     442   IMPLICIT NONE 
     443   ! 
     444   REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtrtemp 
     445   LOGICAL :: check_namelist 
     446   !!---------------------------------------------------------------------- 
     447 
     448   ALLOCATE( tabtrtemp(jpi,jpj,jpk,jptra) ) 
     449 
     450 
     451   ! 1. Declaration of the type of variable which have to be interpolated 
     452   !--------------------------------------------------------------------- 
     453   CALL agrif_declare_var_top 
     454 
     455   ! 2. First interpolations of potentially non zero fields 
     456   !------------------------------------------------------- 
     457   Agrif_SpecialValue=0. 
     458   Agrif_UseSpecialValue = .TRUE. 
     459   Call Agrif_Bc_variable(tabtrtemp,trn_id,calledweight=1.) 
     460   Call Agrif_Bc_variable(tabtrtemp,tra_id,calledweight=1.,procname=interptrn) 
     461   Agrif_UseSpecialValue = .FALSE. 
     462 
     463   ! 3. Some controls 
     464   !----------------- 
     465   check_namelist = .true. 
     466 
     467   IF( check_namelist ) THEN 
     468#  if defined offline      
     469      ! Check time steps 
     470      IF( nint(Agrif_Rhot()) * nint(rdt) .ne. Agrif_Parent(rdt) ) THEN 
     471         WRITE(*,*) 'incompatible time step between grids' 
     472         WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt) 
     473         WRITE(*,*) 'child  grid value : ',nint(rdt) 
     474         WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot() 
     475         STOP 
     476      ENDIF 
     477 
     478      ! Check run length 
     479      IF( Agrif_IRhot() * (Agrif_Parent(nitend)- & 
     480           Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN 
     481         WRITE(*,*) 'incompatible run length between grids' 
     482         WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- & 
     483              Agrif_Parent(nit000)+1),' time step' 
     484         WRITE(*,*) 'child  grid value : ', & 
     485              (nitend-nit000+1),' time step' 
     486         WRITE(*,*) 'value on child grid should be : ', & 
     487              Agrif_IRhot() * (Agrif_Parent(nitend)- & 
     488              Agrif_Parent(nit000)+1) 
     489         STOP 
     490      ENDIF 
     491 
     492      ! Check coordinates 
     493      IF( ln_zps ) THEN 
     494         ! check parameters for partial steps  
     495         IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN 
     496            WRITE(*,*) 'incompatible e3zps_min between grids' 
     497            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
     498            WRITE(*,*) 'child grid  :',e3zps_min 
     499            WRITE(*,*) 'those values should be identical' 
     500            STOP 
     501         ENDIF 
     502         IF( Agrif_Parent(e3zps_rat) .ne. e3zps_rat ) THEN 
     503            WRITE(*,*) 'incompatible e3zps_rat between grids' 
     504            WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
     505            WRITE(*,*) 'child grid  :',e3zps_rat 
     506            WRITE(*,*) 'those values should be identical'                   
     507            STOP 
    182508         ENDIF 
    183509      ENDIF 
    184         
    185       CALL Agrif_Update_tra(0) 
    186       CALL Agrif_Update_dyn(0) 
    187  
    188       nbcline = 0 
    189       ! 
    190       DEALLOCATE(tabtstemp) 
    191       DEALLOCATE(tabuvtemp) 
    192       ! 
    193    END SUBROUTINE Agrif_InitValues_cont 
    194  
    195  
    196    SUBROUTINE agrif_declare_var 
    197       !!---------------------------------------------------------------------- 
    198       !!                 *** ROUTINE agrif_declarE_var *** 
    199       !! 
    200       !! ** Purpose :: Declaration of variables to be interpolated 
    201       !!---------------------------------------------------------------------- 
    202       USE agrif_util 
    203       USE par_oce       !   ONLY : jpts 
    204       USE oce 
    205       IMPLICIT NONE 
    206       !!---------------------------------------------------------------------- 
    207     
    208       ! 1. Declaration of the type of variable which have to be interpolated 
    209       !--------------------------------------------------------------------- 
    210       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) 
    211       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) 
    212       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) 
    213  
    214       CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),un_id) 
    215       CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),vn_id) 
    216       CALL agrif_declare_variable((/1,2,0/),(/2,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),ua_id) 
    217       CALL agrif_declare_variable((/2,1,0/),(/3,2,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj,jpk/),va_id) 
    218     
    219       CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e1u_id) 
    220       CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e2v_id) 
    221  
    222       CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),sshn_id) 
    223       CALL agrif_declare_variable((/2,2/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),gcb_id) 
    224         
    225       ! 2. Type of interpolation 
    226       !------------------------- 
    227       CALL Agrif_Set_bcinterp(tsn_id,interp=AGRIF_linear) 
    228       CALL Agrif_Set_bcinterp(tsa_id,interp=AGRIF_linear) 
    229     
    230       Call Agrif_Set_bcinterp(un_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    231       Call Agrif_Set_bcinterp(vn_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    232  
    233       Call Agrif_Set_bcinterp(ua_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    234       Call Agrif_Set_bcinterp(va_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    235  
    236       Call Agrif_Set_bcinterp(e1u_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    237       Call Agrif_Set_bcinterp(e2v_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    238  
    239       ! 3. Location of interpolation 
    240       !----------------------------- 
    241       Call Agrif_Set_bc(un_id,(/0,1/)) 
    242       Call Agrif_Set_bc(vn_id,(/0,1/)) 
    243  
    244       Call Agrif_Set_bc(e1u_id,(/0,0/)) 
    245       Call Agrif_Set_bc(e2v_id,(/0,0/)) 
    246  
    247       Call Agrif_Set_bc(tsn_id,(/0,1/)) 
    248       Call Agrif_Set_bc(tsa_id,(/-3*Agrif_irhox(),0/)) 
    249  
    250       Call Agrif_Set_bc(ua_id,(/-2*Agrif_irhox(),0/)) 
    251       Call Agrif_Set_bc(va_id,(/-2*Agrif_irhox(),0/)) 
    252  
    253       ! 5. Update type 
    254       !---------------  
    255       Call Agrif_Set_Updatetype(tsn_id, update = AGRIF_Update_Average) 
    256       Call Agrif_Set_Updatetype(tsb_id, update = AGRIF_Update_Average) 
    257  
    258       Call Agrif_Set_Updatetype(sshn_id, update = AGRIF_Update_Average) 
    259       Call Agrif_Set_Updatetype(gcb_id,update = AGRIF_Update_Average) 
    260  
    261       Call Agrif_Set_Updatetype(un_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
    262       Call Agrif_Set_Updatetype(vn_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
    263  
    264       Call Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average) 
    265       Call Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy) 
    266  
    267    END SUBROUTINE agrif_declare_var 
     510#  endif          
     511      ! Check passive tracer cell 
     512      IF( nn_dttrc .ne. 1 ) THEN 
     513         WRITE(*,*) 'nn_dttrc should be equal to 1' 
     514      ENDIF 
     515   ENDIF 
     516 
     517   CALL Agrif_Update_trc(0) 
     518   nbcline_trc = 0 
     519   ! 
     520   DEALLOCATE(tabtrtemp) 
     521   ! 
     522END SUBROUTINE Agrif_InitValues_cont_top 
     523 
     524 
     525SUBROUTINE agrif_declare_var_top 
     526   !!---------------------------------------------------------------------- 
     527   !!                 *** ROUTINE agrif_declare_var_top *** 
     528   !! 
     529   !! ** Purpose :: Declaration of TOP variables to be interpolated 
     530   !!---------------------------------------------------------------------- 
     531   USE agrif_util 
     532   USE dom_oce 
     533   USE trc 
     534 
     535   IMPLICIT NONE 
     536 
     537   ! 1. Declaration of the type of variable which have to be interpolated 
     538   !--------------------------------------------------------------------- 
     539   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) 
     540   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) 
     541   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) 
     542 
     543   ! 2. Type of interpolation 
     544   !------------------------- 
     545   CALL Agrif_Set_bcinterp(trn_id,interp=AGRIF_linear) 
     546   CALL Agrif_Set_bcinterp(tra_id,interp=AGRIF_linear) 
     547 
     548   ! 3. Location of interpolation 
     549   !----------------------------- 
     550   Call Agrif_Set_bc(trn_id,(/0,1/)) 
     551   Call Agrif_Set_bc(tra_id,(/-3*Agrif_irhox(),0/)) 
     552 
     553   ! 5. Update type 
     554   !---------------  
     555   Call Agrif_Set_Updatetype(trn_id, update = AGRIF_Update_Average) 
     556   Call Agrif_Set_Updatetype(trb_id, update = AGRIF_Update_Average) 
     557 
     558 
     559END SUBROUTINE agrif_declare_var_top 
    268560# endif 
    269     
    270 # if defined key_top 
    271    SUBROUTINE Agrif_InitValues_cont_top 
    272       !!---------------------------------------------------------------------- 
    273       !!                 *** ROUTINE Agrif_InitValues_cont_top *** 
    274       !! 
    275       !! ** Purpose :: Declaration of variables to be interpolated 
    276       !!---------------------------------------------------------------------- 
    277       USE Agrif_Util 
    278       USE oce  
    279       USE dom_oce 
    280       USE nemogcm 
    281       USE trc 
    282       USE in_out_manager 
    283       USE agrif_top_update 
    284       USE agrif_top_interp 
    285       USE agrif_top_sponge 
    286       ! 
    287       IMPLICIT NONE 
    288       ! 
    289       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tabtrtemp 
    290       LOGICAL :: check_namelist 
    291       !!---------------------------------------------------------------------- 
    292  
    293       ALLOCATE( tabtrtemp(jpi,jpj,jpk,jptra) ) 
    294        
    295        
    296       ! 1. Declaration of the type of variable which have to be interpolated 
    297       !--------------------------------------------------------------------- 
    298       CALL agrif_declare_var_top 
    299  
    300       ! 2. First interpolations of potentially non zero fields 
    301       !------------------------------------------------------- 
    302       Agrif_SpecialValue=0. 
    303       Agrif_UseSpecialValue = .TRUE. 
    304       Call Agrif_Bc_variable(tabtrtemp,trn_id,calledweight=1.) 
    305       Call Agrif_Bc_variable(tabtrtemp,tra_id,calledweight=1.,procname=interptrn) 
    306       Agrif_UseSpecialValue = .FALSE. 
    307  
    308       ! 3. Some controls 
    309       !----------------- 
    310       check_namelist = .true. 
    311              
    312       IF( check_namelist ) THEN 
    313 #  if defined offline      
    314          ! Check time steps 
    315          IF( nint(Agrif_Rhot()) * nint(rdt) .ne. Agrif_Parent(rdt) ) THEN 
    316             WRITE(*,*) 'incompatible time step between grids' 
    317             WRITE(*,*) 'parent grid value : ',Agrif_Parent(rdt) 
    318             WRITE(*,*) 'child  grid value : ',nint(rdt) 
    319             WRITE(*,*) 'value on parent grid should be : ',rdt*Agrif_Rhot() 
    320             STOP 
    321          ENDIF 
    322  
    323          ! Check run length 
    324          IF( Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    325             Agrif_Parent(nit000)+1) .ne. (nitend-nit000+1) ) THEN 
    326             WRITE(*,*) 'incompatible run length between grids' 
    327             WRITE(*,*) 'parent grid value : ',(Agrif_Parent(nitend)- & 
    328                Agrif_Parent(nit000)+1),' time step' 
    329             WRITE(*,*) 'child  grid value : ', & 
    330                (nitend-nit000+1),' time step' 
    331             WRITE(*,*) 'value on child grid should be : ', & 
    332                Agrif_IRhot() * (Agrif_Parent(nitend)- & 
    333                Agrif_Parent(nit000)+1) 
    334             STOP 
    335          ENDIF 
    336           
    337          ! Check coordinates 
    338          IF( ln_zps ) THEN 
    339             ! check parameters for partial steps  
    340             IF( Agrif_Parent(e3zps_min) .ne. e3zps_min ) THEN 
    341                WRITE(*,*) 'incompatible e3zps_min between grids' 
    342                WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
    343                WRITE(*,*) 'child grid  :',e3zps_min 
    344                WRITE(*,*) 'those values should be identical' 
    345                STOP 
    346             ENDIF           
    347             IF( Agrif_Parent(e3zps_rat) .ne. e3zps_rat ) THEN 
    348                WRITE(*,*) 'incompatible e3zps_rat between grids' 
    349                WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
    350                WRITE(*,*) 'child grid  :',e3zps_rat 
    351                WRITE(*,*) 'those values should be identical'                   
    352                STOP 
    353             ENDIF 
    354          ENDIF 
    355 #  endif          
    356         ! Check passive tracer cell 
    357         IF( nn_dttrc .ne. 1 ) THEN 
    358            WRITE(*,*) 'nn_dttrc should be equal to 1' 
    359         ENDIF 
    360       ENDIF 
    361         
    362       CALL Agrif_Update_trc(0) 
    363       nbcline_trc = 0 
    364       ! 
    365       DEALLOCATE(tabtrtemp) 
    366       ! 
    367    END SUBROUTINE Agrif_InitValues_cont_top 
    368  
    369  
    370    SUBROUTINE agrif_declare_var_top 
    371       !!---------------------------------------------------------------------- 
    372       !!                 *** ROUTINE agrif_declare_var_top *** 
    373       !! 
    374       !! ** Purpose :: Declaration of TOP variables to be interpolated 
    375       !!---------------------------------------------------------------------- 
    376       USE agrif_util 
    377       USE dom_oce 
    378       USE trc 
    379        
    380       IMPLICIT NONE 
    381     
    382       ! 1. Declaration of the type of variable which have to be interpolated 
    383       !--------------------------------------------------------------------- 
    384       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) 
    385       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) 
    386       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) 
    387 #  if defined key_offline 
    388       CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e1u_id) 
    389       CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),e2v_id) 
    390 #  endif 
    391         
    392       ! 2. Type of interpolation 
    393       !------------------------- 
    394       CALL Agrif_Set_bcinterp(trn_id,interp=AGRIF_linear) 
    395       CALL Agrif_Set_bcinterp(tra_id,interp=AGRIF_linear) 
    396     
    397 #  if defined key_offline 
    398       Call Agrif_Set_bcinterp(e1u_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    399       Call Agrif_Set_bcinterp(e2v_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    400 #  endif 
    401  
    402       ! 3. Location of interpolation 
    403       !----------------------------- 
    404 #  if defined key_offline 
    405       Call Agrif_Set_bc(e1u_id,(/0,0/)) 
    406       Call Agrif_Set_bc(e2v_id,(/0,0/)) 
    407 #  endif 
    408       Call Agrif_Set_bc(trn_id,(/0,1/)) 
    409       Call Agrif_Set_bc(tra_id,(/-3*Agrif_irhox(),0/)) 
    410  
    411       ! 5. Update type 
    412       !---------------  
    413       Call Agrif_Set_Updatetype(trn_id, update = AGRIF_Update_Average) 
    414       Call Agrif_Set_Updatetype(trb_id, update = AGRIF_Update_Average) 
    415  
    416 #  if defined key_offline 
    417       Call Agrif_Set_Updatetype(e1u_id,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average) 
    418       Call Agrif_Set_Updatetype(e2v_id,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy) 
    419 #  endif 
    420  
    421    END SUBROUTINE agrif_declare_var_top 
     561 
     562SUBROUTINE Agrif_detect( kg, ksizex ) 
     563   !!---------------------------------------------------------------------- 
     564   !!   *** ROUTINE Agrif_detect *** 
     565   !!---------------------------------------------------------------------- 
     566   USE Agrif_Types 
     567   ! 
     568   INTEGER, DIMENSION(2) :: ksizex 
     569   INTEGER, DIMENSION(ksizex(1),ksizex(2)) :: kg  
     570   !!---------------------------------------------------------------------- 
     571   ! 
     572   RETURN 
     573   ! 
     574END SUBROUTINE Agrif_detect 
     575 
     576 
     577SUBROUTINE agrif_nemo_init 
     578   !!---------------------------------------------------------------------- 
     579   !!                     *** ROUTINE agrif_init *** 
     580   !!---------------------------------------------------------------------- 
     581   USE agrif_oce  
     582   USE agrif_ice 
     583   USE in_out_manager 
     584   USE lib_mpp 
     585   IMPLICIT NONE 
     586   ! 
     587   NAMELIST/namagrif/ nn_cln_update, rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn 
     588   !!---------------------------------------------------------------------- 
     589   ! 
     590   REWIND( numnam )                ! Read namagrif namelist 
     591   READ  ( numnam, namagrif ) 
     592   ! 
     593   IF(lwp) THEN                    ! control print 
     594      WRITE(numout,*) 
     595      WRITE(numout,*) 'agrif_nemo_init : AGRIF parameters' 
     596      WRITE(numout,*) '~~~~~~~~~~~~~~~' 
     597      WRITE(numout,*) '   Namelist namagrif : set AGRIF parameters' 
     598      WRITE(numout,*) '      baroclinic update frequency       nn_cln_update = ', nn_cln_update 
     599      WRITE(numout,*) '      sponge coefficient for tracers    rn_sponge_tra = ', rn_sponge_tra, ' s' 
     600      WRITE(numout,*) '      sponge coefficient for dynamics   rn_sponge_tra = ', rn_sponge_dyn, ' s' 
     601      WRITE(numout,*) '      use special values for dynamics   ln_spc_dyn    = ', ln_spc_dyn 
     602      WRITE(numout,*)  
     603   ENDIF 
     604   ! 
     605   ! convert DOCTOR namelist name into OLD names 
     606   nbclineupdate = nn_cln_update 
     607   visc_tra      = rn_sponge_tra 
     608   visc_dyn      = rn_sponge_dyn 
     609   ! 
     610   IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif sol_oce_alloc: allocation of arrays failed') 
     611# if defined key_lim2 
     612   IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') 
    422613# endif 
    423     
    424    SUBROUTINE Agrif_detect( kg, ksizex ) 
    425       !!---------------------------------------------------------------------- 
    426       !!   *** ROUTINE Agrif_detect *** 
    427       !!---------------------------------------------------------------------- 
    428       USE Agrif_Types 
    429       ! 
    430       INTEGER, DIMENSION(2) :: ksizex 
    431       INTEGER, DIMENSION(ksizex(1),ksizex(2)) :: kg  
    432       !!---------------------------------------------------------------------- 
    433       ! 
    434       RETURN 
    435       ! 
    436    END SUBROUTINE Agrif_detect 
    437  
    438  
    439    SUBROUTINE agrif_nemo_init 
    440       !!---------------------------------------------------------------------- 
    441       !!                     *** ROUTINE agrif_init *** 
    442       !!---------------------------------------------------------------------- 
    443       USE agrif_oce  
    444       USE in_out_manager 
    445       USE lib_mpp 
    446       IMPLICIT NONE 
    447       ! 
    448       NAMELIST/namagrif/ nn_cln_update, rn_sponge_tra, rn_sponge_dyn, ln_spc_dyn 
    449       !!---------------------------------------------------------------------- 
    450       ! 
    451       REWIND( numnam )                ! Read namagrif namelist 
    452       READ  ( numnam, namagrif ) 
    453       ! 
    454       IF(lwp) THEN                    ! control print 
    455          WRITE(numout,*) 
    456          WRITE(numout,*) 'agrif_nemo_init : AGRIF parameters' 
    457          WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    458          WRITE(numout,*) '   Namelist namagrif : set AGRIF parameters' 
    459          WRITE(numout,*) '      baroclinic update frequency       nn_cln_update = ', nn_cln_update 
    460          WRITE(numout,*) '      sponge coefficient for tracers    rn_sponge_tra = ', rn_sponge_tra, ' s' 
    461          WRITE(numout,*) '      sponge coefficient for dynamics   rn_sponge_tra = ', rn_sponge_dyn, ' s' 
    462          WRITE(numout,*) '      use special values for dynamics   ln_spc_dyn    = ', ln_spc_dyn 
    463          WRITE(numout,*)  
    464       ENDIF 
    465       ! 
    466       ! convert DOCTOR namelist name into OLD names 
    467       nbclineupdate = nn_cln_update 
    468       visc_tra      = rn_sponge_tra 
    469       visc_dyn      = rn_sponge_dyn 
    470       ! 
    471       IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif sol_oce_alloc: allocation of arrays failed') 
    472       ! 
    473     END SUBROUTINE agrif_nemo_init 
     614   ! 
     615END SUBROUTINE agrif_nemo_init 
    474616 
    475617# if defined key_mpp_mpi 
    476618 
    477    SUBROUTINE Agrif_InvLoc( indloc, nprocloc, i, indglob ) 
    478       !!---------------------------------------------------------------------- 
    479       !!                     *** ROUTINE Agrif_detect *** 
    480       !!---------------------------------------------------------------------- 
    481       USE dom_oce 
    482       IMPLICIT NONE 
    483       ! 
    484       INTEGER :: indglob, indloc, nprocloc, i 
    485       !!---------------------------------------------------------------------- 
    486       ! 
    487       SELECT CASE( i ) 
    488       CASE(1)   ;   indglob = indloc + nimppt(nprocloc+1) - 1 
    489       CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1  
    490       CASE(3)   ;   indglob = indloc 
    491       CASE(4)   ;   indglob = indloc 
    492       END SELECT 
    493       ! 
    494    END SUBROUTINE Agrif_InvLoc 
     619SUBROUTINE Agrif_InvLoc( indloc, nprocloc, i, indglob ) 
     620   !!---------------------------------------------------------------------- 
     621   !!                     *** ROUTINE Agrif_detect *** 
     622   !!---------------------------------------------------------------------- 
     623   USE dom_oce 
     624   IMPLICIT NONE 
     625   ! 
     626   INTEGER :: indglob, indloc, nprocloc, i 
     627   !!---------------------------------------------------------------------- 
     628   ! 
     629   SELECT CASE( i ) 
     630   CASE(1)   ;   indglob = indloc + nimppt(nprocloc+1) - 1 
     631   CASE(2)   ;   indglob = indloc + njmppt(nprocloc+1) - 1  
     632   CASE(3)   ;   indglob = indloc 
     633   CASE(4)   ;   indglob = indloc 
     634   END SELECT 
     635   ! 
     636END SUBROUTINE Agrif_InvLoc 
    495637 
    496638# endif 
    497639 
    498640#else 
    499    SUBROUTINE Subcalledbyagrif 
    500       !!---------------------------------------------------------------------- 
    501       !!                   *** ROUTINE Subcalledbyagrif *** 
    502       !!---------------------------------------------------------------------- 
    503       WRITE(*,*) 'Impossible to be here' 
    504    END SUBROUTINE Subcalledbyagrif 
     641SUBROUTINE Subcalledbyagrif 
     642   !!---------------------------------------------------------------------- 
     643   !!                   *** ROUTINE Subcalledbyagrif *** 
     644   !!---------------------------------------------------------------------- 
     645   WRITE(*,*) 'Impossible to be here' 
     646END SUBROUTINE Subcalledbyagrif 
    505647#endif 
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r3294 r3454  
    4848   USE in_out_manager   ! I/O manager 
    4949   USE prtctl           ! Print control 
     50 
     51# if defined key_agrif 
     52   USE agrif_ice 
     53   USE agrif_lim2_update 
     54# endif 
    5055 
    5156   IMPLICIT NONE 
     
    101106         ! 
    102107         CALL ice_init_2 
     108         ! 
     109# if defined key_agrif 
     110         IF( .NOT. Agrif_Root() ) CALL Agrif_InitValues_cont_lim2   ! AGRIF: set the meshes 
     111# endif 
    103112      ENDIF 
    104113 
     
    106115      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !  Ice time-step only  ! 
    107116         !                                     !----------------------! 
     117# if defined key_agrif 
     118         IF( .NOT. Agrif_Root() ) lim_nbstep = MOD(lim_nbstep,Agrif_rhot()& 
     119         &*Agrif_PArent(nn_fsbc)/REAL(nn_fsbc)) + 1 
     120# endif 
    108121         !  Bulk Formulea ! 
    109122         !----------------! 
     
    211224         IF( lrst_ice  )   CALL lim_rst_write_2( kt )      ! Ice restart file 
    212225         ! 
     226# if defined key_agrif && defined key_lim2 
     227         IF( .NOT. Agrif_Root() )   CALL agrif_update_lim2( kt ) 
     228# endif 
     229         ! 
    213230      ENDIF                                    ! End sea-ice time step only 
    214231      ! 
  • branches/2012/dev_r3387_LOCEAN6_AGRIF_LIM/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r3352 r3454  
    116116      !                            !-----------------------! 
    117117#if defined key_agrif 
    118       CALL Agrif_Declare_Var       ! AGRIF: set the meshes 
     118      CALL Agrif_Declare_Var_dom   ! AGRIF: set the meshes for DOM 
     119      CALL Agrif_Declare_Var       !  "      "   "   "      "  DYN/TRA  
     120# if defined key_lim2 
     121      CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM 
     122# endif 
    119123# if defined key_top 
    120       CALL Agrif_Declare_Var_Top   ! AGRIF: set the meshes 
     124      CALL Agrif_Declare_Var_top   !  "      "   "   "      "  TOP 
    121125# endif 
    122126#endif 
Note: See TracChangeset for help on using the changeset viewer.