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

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

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

    r6140 r7646  
    11#if defined key_agrif 
    22!!---------------------------------------------------------------------- 
    3 !! NEMO/NST 3.7 , NEMO Consortium (2015) 
     3!! NEMO/NST 3.7 , NEMO Consortium (2016) 
    44!! $Id$ 
    55!! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     
    1818   USE dom_oce 
    1919   USE nemogcm 
    20    ! 
     20   !! 
    2121   IMPLICIT NONE 
    2222   !!---------------------------------------------------------------------- 
     
    3232! JC: change to allow for different vertical levels 
    3333!     jpk is already set 
    34 !     keep it jpk possibly different from jpkdta which  
     34!     keep it jpk possibly different from jpkglo which  
    3535!     hold parent grid vertical levels number (set earlier) 
    36 !      jpk     = jpkdta  
     36!      jpk     = jpkglo  
    3737      jpim1   = jpi-1  
    3838      jpjm1   = jpj-1  
    3939      jpkm1   = jpk-1                                          
    4040      jpij    = jpi*jpj  
    41       jpidta  = jpiglo 
    42       jpjdta  = jpjglo 
    43       jpizoom = 1 
    44       jpjzoom = 1 
    4541      nperio  = 0 
    4642      jperio  = 0 
     
    6157   USE nemogcm 
    6258   USE tradmp 
    63    USE bdy_par 
    64  
    65    IMPLICIT NONE 
    66    !!---------------------------------------------------------------------- 
    67    ! 0. Initializations 
    68    !------------------- 
    69    IF( cp_cfg == 'orca' ) THEN 
    70       IF ( jp_cfg == 2 .OR. jp_cfg == 025 .OR. jp_cfg == 05 & 
    71             &                      .OR. jp_cfg == 4 ) THEN 
    72          jp_cfg = -1    ! set special value for jp_cfg on fine grids 
    73          cp_cfg = "default" 
     59   USE bdy_oce   , ONLY: ln_bdy 
     60   !! 
     61   IMPLICIT NONE 
     62   !!---------------------------------------------------------------------- 
     63   ! 
     64!!gm  I think this is now useless ...   nn_cfg & cn_cfg are set to -999999 and "UNKNOWN"  
     65!!gm                                    when reading the AGRIF domain configuration file 
     66   IF( cn_cfg == 'orca' ) THEN 
     67      IF ( nn_cfg == 2 .OR. nn_cfg == 025 .OR. nn_cfg == 05  .OR. nn_cfg == 4 ) THEN 
     68         nn_cfg = -1    ! set special value for nn_cfg on fine grids 
     69         cn_cfg = "default" 
    7470      ENDIF 
    7571   ENDIF 
    76    ! Specific fine grid Initializations 
    77    ! no tracer damping on fine grids 
    78    ln_tradmp = .FALSE. 
    79    ! no open boundary on fine grids 
    80    lk_bdy = .FALSE. 
    81  
    82  
    83    CALL nemo_init  ! Initializations of each fine grid 
    84  
     72   !                    !* Specific fine grid Initializations 
     73   ln_tradmp = .FALSE.        ! no tracer damping on fine grids 
     74   ! 
     75   ln_bdy    = .FALSE.        ! no open boundary on fine grids 
     76 
     77   CALL nemo_init       !* Initializations of each fine grid 
     78 
     79   !                    !* Agrif initialization 
    8580   CALL agrif_nemo_init 
    8681   CALL Agrif_InitValues_cont_dom 
    87 # if ! defined key_offline 
    8882   CALL Agrif_InitValues_cont 
    89 # endif        
    9083# if defined key_top 
    9184   CALL Agrif_InitValues_cont_top 
    92 # endif       
     85# endif 
     86   ! 
    9387END SUBROUTINE Agrif_initvalues 
    9488 
     
    108102   USE agrif_opa_interp 
    109103   USE agrif_opa_sponge 
    110    ! 
    111    IMPLICIT NONE 
    112    ! 
    113    !!---------------------------------------------------------------------- 
    114  
     104   !! 
     105   IMPLICIT NONE 
     106   !!---------------------------------------------------------------------- 
     107   ! 
    115108   ! Declaration of the type of variable which have to be interpolated 
    116    !--------------------------------------------------------------------- 
     109   ! 
    117110   CALL agrif_declare_var_dom 
    118111   ! 
     
    129122   USE par_oce        
    130123   USE oce 
     124   !! 
    131125   IMPLICIT NONE 
    132126   !!---------------------------------------------------------------------- 
     
    158152END SUBROUTINE agrif_declare_var_dom 
    159153 
    160  
    161 # if ! defined key_offline 
    162154 
    163155SUBROUTINE Agrif_InitValues_cont 
     
    176168   USE agrif_opa_interp 
    177169   USE agrif_opa_sponge 
    178    ! 
     170   !! 
    179171   IMPLICIT NONE 
    180172   ! 
     
    239231         WRITE(cl_check2,*)  NINT(rdt) 
    240232         WRITE(cl_check3,*)  NINT(Agrif_Parent(rdt)/Agrif_Rhot()) 
    241          CALL ctl_warn( 'incompatible time step between grids',   & 
     233         CALL ctl_stop( 'incompatible time step between ocean grids',   & 
    242234               &               'parent grid value : '//cl_check1    ,   &  
    243235               &               'child  grid value : '//cl_check2    ,   &  
    244                &               'value on child grid will be changed to : '//cl_check3 ) 
    245          rdt=Agrif_Parent(rdt)/Agrif_Rhot() 
     236               &               'value on child grid should be changed to : '//cl_check3 ) 
    246237      ENDIF 
    247238 
     
    259250 
    260251      ! Check coordinates 
    261       IF( ln_zps ) THEN 
    262          ! check parameters for partial steps  
    263          IF( Agrif_Parent(e3zps_min) .NE. e3zps_min ) THEN 
    264             WRITE(*,*) 'incompatible e3zps_min between grids' 
    265             WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
    266             WRITE(*,*) 'child grid  :',e3zps_min 
    267             WRITE(*,*) 'those values should be identical' 
    268             STOP 
    269          ENDIF 
    270          IF( Agrif_Parent(e3zps_rat) /= e3zps_rat ) THEN 
    271             WRITE(*,*) 'incompatible e3zps_rat between grids' 
    272             WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
    273             WRITE(*,*) 'child grid  :',e3zps_rat 
    274             WRITE(*,*) 'those values should be identical'                   
    275             STOP 
    276          ENDIF 
    277       ENDIF 
     252     !SF IF( ln_zps ) THEN 
     253     !SF     ! check parameters for partial steps  
     254     !SF     IF( Agrif_Parent(e3zps_min) .NE. e3zps_min ) THEN 
     255     !SF        WRITE(*,*) 'incompatible e3zps_min between grids' 
     256     !SF        WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_min) 
     257     !SF        WRITE(*,*) 'child grid  :',e3zps_min 
     258     !SF        WRITE(*,*) 'those values should be identical' 
     259     !SF        STOP 
     260     !SF     ENDIF 
     261     !SF     IF( Agrif_Parent(e3zps_rat) /= e3zps_rat ) THEN 
     262     !SF        WRITE(*,*) 'incompatible e3zps_rat between grids' 
     263     !SF        WRITE(*,*) 'parent grid :',Agrif_Parent(e3zps_rat) 
     264     !SF        WRITE(*,*) 'child grid  :',e3zps_rat 
     265     !SF        WRITE(*,*) 'those values should be identical'                   
     266     !SF        STOP 
     267     !SF     ENDIF 
     268     !SF ENDIF 
    278269 
    279270      ! Check free surface scheme 
     
    346337   USE oce 
    347338   USE agrif_oce 
     339   !! 
    348340   IMPLICIT NONE 
    349341   !!---------------------------------------------------------------------- 
     
    468460   ! 
    469461END SUBROUTINE agrif_declare_var 
    470 # endif 
    471462 
    472463#  if defined key_lim2 
     
    484475   USE agrif_lim2_interp 
    485476   USE lib_mpp 
    486    ! 
    487    IMPLICIT NONE 
    488    ! 
     477   !! 
     478   IMPLICIT NONE 
    489479   !!---------------------------------------------------------------------- 
    490480 
     
    521511END SUBROUTINE Agrif_InitValues_cont_lim2 
    522512 
     513 
    523514SUBROUTINE agrif_declare_var_lim2 
    524515   !!---------------------------------------------------------------------- 
     
    529520   USE agrif_util 
    530521   USE ice_2 
    531  
     522   !! 
    532523   IMPLICIT NONE 
    533524   !!---------------------------------------------------------------------- 
     
    564555END SUBROUTINE agrif_declare_var_lim2 
    565556#  endif 
     557 
     558#if defined key_lim3 
     559SUBROUTINE Agrif_InitValues_cont_lim3 
     560   !!---------------------------------------------------------------------- 
     561   !!                 *** ROUTINE Agrif_InitValues_cont_lim3 *** 
     562   !! 
     563   !! ** Purpose :: Initialisation of variables to be interpolated for LIM3 
     564   !!---------------------------------------------------------------------- 
     565   USE Agrif_Util 
     566   USE sbc_oce, ONLY : nn_fsbc  ! clem: necessary otherwise Agrif_Parent(nn_fsbc) = nn_fsbc 
     567   USE ice 
     568   USE agrif_ice 
     569   USE in_out_manager 
     570   USE agrif_lim3_update 
     571   USE agrif_lim3_interp 
     572   USE lib_mpp 
     573   ! 
     574   IMPLICIT NONE 
     575   !!---------------------------------------------------------------------- 
     576   ! 
     577   ! Declaration of the type of variable which have to be interpolated (parent=>child) 
     578   !---------------------------------------------------------------------------------- 
     579   CALL agrif_declare_var_lim3 
     580 
     581   ! Controls (clem) 
     582   ! stop if rhot * nn_fsbc(parent) /= N * nn_fsbc(child) with N being integer 
     583   IF( MOD( Agrif_irhot() * Agrif_Parent(nn_fsbc), nn_fsbc ) /= 0 )  THEN 
     584      CALL ctl_stop('rhot * nn_fsbc(parent) /= N * nn_fsbc(child), therefore nn_fsbc(child) should be set to 1 or nn_fsbc(parent)') 
     585   ENDIF 
     586 
     587   ! stop if update frequency is different from nn_fsbc 
     588   IF( nbclineupdate > nn_fsbc )  CALL ctl_stop('With ice model on child grid, nn_cln_update should be set to 1 or nn_fsbc') 
     589 
     590 
     591   ! First Interpolations (using "after" ice subtime step => lim_nbstep=1) 
     592   !---------------------------------------------------------------------- 
     593   lim_nbstep = 1 
     594   CALL agrif_interp_lim3('U') ! interpolation of ice velocities 
     595   CALL agrif_interp_lim3('V') ! interpolation of ice velocities 
     596   CALL agrif_interp_lim3('T') ! interpolation of ice tracers 
     597   lim_nbstep = 0 
     598    
     599   ! Update in case 2 ways 
     600   !---------------------- 
     601   CALL agrif_update_lim3(0) 
     602 
     603   ! 
     604END SUBROUTINE Agrif_InitValues_cont_lim3 
     605 
     606SUBROUTINE agrif_declare_var_lim3 
     607   !!---------------------------------------------------------------------- 
     608   !!                 *** ROUTINE agrif_declare_var_lim3 *** 
     609   !! 
     610   !! ** Purpose :: Declaration of variables to be interpolated for LIM3 
     611   !!---------------------------------------------------------------------- 
     612   USE Agrif_Util 
     613   USE ice 
     614 
     615   IMPLICIT NONE 
     616   !!---------------------------------------------------------------------- 
     617   ! 
     618   ! 1. Declaration of the type of variable which have to be interpolated (parent=>child) 
     619   !       agrif_declare_variable(position,1st point index,--,--,dimensions,name) 
     620   !------------------------------------------------------------------------------------- 
     621   CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/nlci,nlcj,jpl*(5+nlay_s+nlay_i)/),tra_ice_id ) 
     622   CALL agrif_declare_variable((/1,2/)    ,(/2,3/),(/'x','y'/)    ,(/1,1/)  ,(/nlci,nlcj/)                      ,u_ice_id   ) 
     623   CALL agrif_declare_variable((/2,1/)    ,(/3,2/),(/'x','y'/)    ,(/1,1/)  ,(/nlci,nlcj/)                      ,v_ice_id   ) 
     624 
     625   ! 2. Set interpolations (normal & tangent to the grid cell for velocities) 
     626   !----------------------------------- 
     627   CALL Agrif_Set_bcinterp(tra_ice_id,  interp = AGRIF_linear) 
     628   CALL Agrif_Set_bcinterp(u_ice_id  , interp1 = Agrif_linear,interp2 = AGRIF_ppm   ) 
     629   CALL Agrif_Set_bcinterp(v_ice_id  , interp1 = AGRIF_ppm   ,interp2 = Agrif_linear) 
     630 
     631   ! 3. Set location of interpolations 
     632   !---------------------------------- 
     633   CALL Agrif_Set_bc(tra_ice_id,(/0,1/)) 
     634   CALL Agrif_Set_bc(u_ice_id  ,(/0,1/)) 
     635   CALL Agrif_Set_bc(v_ice_id  ,(/0,1/)) 
     636 
     637   ! 4. Set update type in case 2 ways (child=>parent) (normal & tangent to the grid cell for velocities) 
     638   !-------------------------------------------------- 
     639   CALL Agrif_Set_Updatetype(tra_ice_id, update = AGRIF_Update_Average) ! clem je comprends pas average/copy 
     640   CALL Agrif_Set_Updatetype(u_ice_id  ,update1 = Agrif_Update_Copy   , update2 = Agrif_Update_Average) 
     641   CALL Agrif_Set_Updatetype(v_ice_id  ,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy   ) 
     642 
     643END SUBROUTINE agrif_declare_var_lim3 
     644#endif 
    566645 
    567646 
     
    585664   USE agrif_top_interp 
    586665   USE agrif_top_sponge 
    587    ! 
     666   !! 
    588667   IMPLICIT NONE 
    589668   ! 
     
    615694 
    616695   IF( check_namelist ) THEN 
    617 # if defined key_offline 
    618696      ! Check time steps 
    619697      IF( NINT(Agrif_Rhot()) * NINT(rdt) .NE. Agrif_Parent(rdt) ) THEN 
     
    621699         WRITE(cl_check2,*)  rdt 
    622700         WRITE(cl_check3,*)  rdt*Agrif_Rhot() 
    623          CALL ctl_warn( 'incompatible time step between grids',   & 
     701         CALL ctl_stop( 'incompatible time step between grids',   & 
    624702               &               'parent grid value : '//cl_check1    ,   &  
    625703               &               'child  grid value : '//cl_check2    ,   &  
    626                &               'value on child grid will be changed to  & 
     704               &               'value on child grid should be changed to  & 
    627705               &               :'//cl_check3  ) 
    628          rdt=rdt*Agrif_Rhot() 
    629706      ENDIF 
    630707 
     
    659736         ENDIF 
    660737      ENDIF 
    661 #  endif          
    662738      ! Check passive tracer cell 
    663739      IF( nn_dttrc .NE. 1 ) THEN 
     
    684760   USE dom_oce 
    685761   USE trc 
    686  
    687    IMPLICIT NONE 
     762   !! 
     763   IMPLICIT NONE 
     764   !!---------------------------------------------------------------------- 
    688765 
    689766   ! 1. Declaration of the type of variable which have to be interpolated 
     
    716793SUBROUTINE Agrif_detect( kg, ksizex ) 
    717794   !!---------------------------------------------------------------------- 
    718    !!   *** ROUTINE Agrif_detect *** 
    719    !!---------------------------------------------------------------------- 
    720    ! 
     795   !!                      *** ROUTINE Agrif_detect *** 
     796   !!---------------------------------------------------------------------- 
    721797   INTEGER, DIMENSION(2) :: ksizex 
    722798   INTEGER, DIMENSION(ksizex(1),ksizex(2)) :: kg  
     
    736812   USE in_out_manager 
    737813   USE lib_mpp 
     814   !! 
    738815   IMPLICIT NONE 
    739816   ! 
     
    777854   IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif agrif_oce_alloc: allocation of arrays failed') 
    778855# if defined key_lim2 
    779    IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') 
     856   IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') ! only for LIM2 (not LIM3) 
    780857# endif 
    781858   ! 
     
    789866   !!---------------------------------------------------------------------- 
    790867   USE dom_oce 
     868   !! 
    791869   IMPLICIT NONE 
    792870   ! 
     
    803881END SUBROUTINE Agrif_InvLoc 
    804882 
     883 
    805884SUBROUTINE Agrif_get_proc_info( imin, imax, jmin, jmax ) 
    806885   !!---------------------------------------------------------------------- 
     
    808887   !!---------------------------------------------------------------------- 
    809888   USE par_oce 
     889   !! 
    810890   IMPLICIT NONE 
    811891   ! 
     
    821901END SUBROUTINE Agrif_get_proc_info 
    822902 
     903 
    823904SUBROUTINE Agrif_estimate_parallel_cost(imin, imax,jmin, jmax, nbprocs, grid_cost) 
    824905   !!---------------------------------------------------------------------- 
     
    826907   !!---------------------------------------------------------------------- 
    827908   USE par_oce 
     909   !! 
    828910   IMPLICIT NONE 
    829911   ! 
Note: See TracChangeset for help on using the changeset viewer.