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 8306 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/NST_SRC – NEMO

Ignore:
Timestamp:
2017-07-10T12:18:03+02:00 (7 years ago)
Author:
clem
Message:

step1: remove LIM2 from the code

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/NST_SRC
Files:
2 deleted
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/NST_SRC/agrif_ice.F90

    r7646 r8306  
    77   !!            3.6  ! 2016-05  (C. Rousset)   Add LIM3 compatibility 
    88   !!---------------------------------------------------------------------- 
    9 #if defined key_agrif && defined key_lim2 
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_agrif'                                              AGRIF zoom 
    12    !!---------------------------------------------------------------------- 
    13    USE par_oce      ! ocean parameters 
    14     
    15    IMPLICIT NONE 
    16    PRIVATE  
    17  
    18    PUBLIC agrif_ice_alloc ! routine called by nemo_init in nemogcm.F90 
    19  
    20    INTEGER, PUBLIC :: u_ice_id, v_ice_id, adv_ice_id 
    21    REAL(wp), PUBLIC :: lim_nbstep = 0.    ! child time position in sea-ice model 
    22 #if defined key_lim2_vp 
    23    REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:)     :: u_ice_nst, v_ice_nst    
    24 #else 
    25    REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)   :: u_ice_oe, u_ice_sn     !: boundaries arrays 
    26    REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:)   :: v_ice_oe, v_ice_sn     !:  "          "  
    27 #endif 
    28    REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:,:) :: adv_ice_oe, adv_ice_sn !:  "          " 
    29  
    30    !!---------------------------------------------------------------------- 
    31    !! NEMO/NST 3.3.4 , NEMO Consortium (2012) 
    32    !! $Id$ 
    33    !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    34    !!---------------------------------------------------------------------- 
    35  
    36 CONTAINS  
    37  
    38    INTEGER FUNCTION agrif_ice_alloc() 
    39       !!---------------------------------------------------------------------- 
    40       !!                ***  FUNCTION agrif_ice_alloc  *** 
    41       !!---------------------------------------------------------------------- 
    42 #if defined key_lim2_vp 
    43       ALLOCATE( u_ice_nst(jpi,jpj), v_ice_nst(jpi,jpj) ,   & 
    44 #else 
    45       ALLOCATE( u_ice_oe(4,jpj,2) , v_ice_oe(4,jpj,2) ,    & 
    46          &      u_ice_sn(jpi,4,2) , v_ice_sn(jpi,4,2) ,    & 
    47 #endif 
    48          &      adv_ice_oe (4,jpj,7,2) , adv_ice_sn (jpi,4,7,2) ,   & 
    49          &      STAT = agrif_ice_alloc) 
    50  
    51 #if ! defined key_lim2_vp 
    52       u_ice_oe(:,:,:) =  0.e0 
    53       v_ice_oe(:,:,:) =  0.e0 
    54       u_ice_sn(:,:,:) =  0.e0 
    55       v_ice_sn(:,:,:) =  0.e0 
    56 #endif 
    57       adv_ice_oe (:,:,:,:) = 0.e0  
    58       adv_ice_sn (:,:,:,:) = 0.e0  
    59       ! 
    60    END FUNCTION agrif_ice_alloc 
    61  
    62 #elif defined key_agrif && defined key_lim3 
     9#if defined key_agrif && defined key_lim3 
    6310   !!---------------------------------------------------------------------- 
    6411   !!   'key_agrif'                                              AGRIF zoom 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r8226 r8306  
    481481END SUBROUTINE agrif_declare_var 
    482482 
    483 #  if defined key_lim2 
    484 SUBROUTINE Agrif_InitValues_cont_lim2 
    485    !!---------------------------------------------------------------------- 
    486    !!                 *** ROUTINE Agrif_InitValues_cont_lim2 *** 
    487    !! 
    488    !! ** Purpose :: Initialisation of variables to be interpolated for LIM2 
    489    !!---------------------------------------------------------------------- 
    490    USE Agrif_Util 
    491    USE ice_2 
    492    USE agrif_ice 
    493    USE in_out_manager 
    494    USE agrif_lim2_update 
    495    USE agrif_lim2_interp 
    496    USE lib_mpp 
    497    !! 
    498    IMPLICIT NONE 
    499    !!---------------------------------------------------------------------- 
    500  
    501    ! 1. Declaration of the type of variable which have to be interpolated 
    502    !--------------------------------------------------------------------- 
    503    CALL agrif_declare_var_lim2 
    504  
    505    ! 2. First interpolations of potentially non zero fields 
    506    !------------------------------------------------------- 
    507    Agrif_SpecialValue=-9999. 
    508    Agrif_UseSpecialValue = .TRUE. 
    509    !     Call Agrif_Bc_variable(zadv ,adv_ice_id ,calledweight=1.,procname=interp_adv_ice ) 
    510    !     Call Agrif_Bc_variable(zvel ,u_ice_id   ,calledweight=1.,procname=interp_u_ice   ) 
    511    !     Call Agrif_Bc_variable(zvel ,v_ice_id   ,calledweight=1.,procname=interp_v_ice   ) 
    512    Agrif_SpecialValue=0. 
    513    Agrif_UseSpecialValue = .FALSE. 
    514  
    515    ! 3. Some controls 
    516    !----------------- 
    517  
    518 #   if ! defined key_lim2_vp 
    519    lim_nbstep = 1. 
    520    CALL agrif_rhg_lim2_load 
    521    CALL agrif_trp_lim2_load 
    522    lim_nbstep = 0. 
    523 #   endif 
    524    !RB mandatory but why ??? 
    525    !      IF( nbclineupdate /= nn_fsbc .AND. nn_ice == 2 )THEN 
    526    !         CALL ctl_warn ('With ice model on child grid, nbclineupdate is set to nn_fsbc') 
    527    !         nbclineupdate = nn_fsbc 
    528    !       ENDIF 
    529    CALL Agrif_Update_lim2(0) 
    530    ! 
    531 END SUBROUTINE Agrif_InitValues_cont_lim2 
    532  
    533  
    534 SUBROUTINE agrif_declare_var_lim2 
    535    !!---------------------------------------------------------------------- 
    536    !!                 *** ROUTINE agrif_declare_var_lim2 *** 
    537    !! 
    538    !! ** Purpose :: Declaration of variables to be interpolated for LIM2 
    539    !!---------------------------------------------------------------------- 
    540    USE agrif_util 
    541    USE ice_2 
    542    !! 
    543    IMPLICIT NONE 
    544    !!---------------------------------------------------------------------- 
    545  
    546    ! 1. Declaration of the type of variable which have to be interpolated 
    547    !--------------------------------------------------------------------- 
    548    CALL agrif_declare_variable((/2,2,0/),(/3,3,0/),(/'x','y','N'/),(/1,1,1/),(/jpi,jpj, 7/),adv_ice_id ) 
    549 #   if defined key_lim2_vp 
    550    CALL agrif_declare_variable((/1,1/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),u_ice_id) 
    551    CALL agrif_declare_variable((/1,1/),(/3,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),v_ice_id) 
    552 #   else 
    553    CALL agrif_declare_variable((/1,2/),(/2,3/),(/'x','y'/),(/1,1/),(/jpi,jpj/),u_ice_id) 
    554    CALL agrif_declare_variable((/2,1/),(/3,2/),(/'x','y'/),(/1,1/),(/jpi,jpj/),v_ice_id) 
    555 #   endif 
    556  
    557    ! 2. Type of interpolation 
    558    !------------------------- 
    559    CALL Agrif_Set_bcinterp(adv_ice_id ,interp=AGRIF_linear) 
    560    CALL Agrif_Set_bcinterp(u_ice_id,interp1=Agrif_linear,interp2=AGRIF_ppm) 
    561    CALL Agrif_Set_bcinterp(v_ice_id,interp1=AGRIF_ppm,interp2=Agrif_linear) 
    562  
    563    ! 3. Location of interpolation 
    564    !----------------------------- 
    565    CALL Agrif_Set_bc(adv_ice_id ,(/0,1/)) 
    566    CALL Agrif_Set_bc(u_ice_id,(/0,1/)) 
    567    CALL Agrif_Set_bc(v_ice_id,(/0,1/)) 
    568  
    569    ! 5. Update type 
    570    !--------------- 
    571    CALL Agrif_Set_Updatetype(adv_ice_id , update = AGRIF_Update_Average) 
    572    CALL Agrif_Set_Updatetype(u_ice_id,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
    573    CALL Agrif_Set_Updatetype(v_ice_id,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
    574    !  
    575 END SUBROUTINE agrif_declare_var_lim2 
    576 #  endif 
    577  
    578483#if defined key_lim3 
    579484SUBROUTINE Agrif_InitValues_cont_lim3 
     
    902807   ! 
    903808   IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif agrif_oce_alloc: allocation of arrays failed') 
    904 # if defined key_lim2 
    905    IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') ! only for LIM2 (not LIM3) 
    906 # endif 
    907809   ! 
    908810END SUBROUTINE agrif_nemo_init 
Note: See TracChangeset for help on using the changeset viewer.