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 6584 – NEMO

Changeset 6584


Ignore:
Timestamp:
2016-05-20T11:54:18+02:00 (8 years ago)
Author:
clem
Message:

LIM3 and Agrif compatibility

Location:
branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO
Files:
2 added
9 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r5888 r6584  
    4040#if defined key_agrif && defined key_lim2 
    4141   USE agrif_lim2_interp 
     42#endif 
     43#if defined key_agrif && defined key_lim3 
     44   USE agrif_lim3_interp 
    4245#endif 
    4346#if defined key_bdy 
     
    174177      CALL agrif_rhg_lim2_load      ! First interpolation of coarse values 
    175178#endif 
     179#if defined key_agrif && defined key_lim3  
     180      CALL agrif_interp_lim3('U')   ! First interpolation of coarse values 
     181      CALL agrif_interp_lim3('V')   ! First interpolation of coarse values 
     182#endif 
    176183      ! 
    177184      !------------------------------------------------------------------------------! 
     
    460467            CALL agrif_rhg_lim2( jter, nn_nevp, 'U' ) 
    461468#endif 
     469#if defined key_agrif && defined key_lim3 
     470            CALL agrif_interp_lim3( 'U' ) 
     471#endif 
    462472#if defined key_bdy 
    463473         CALL bdy_ice_lim_dyn( 'U' ) 
     
    486496            CALL agrif_rhg_lim2( jter, nn_nevp, 'V' ) 
    487497#endif 
     498#if defined key_agrif && defined key_lim3 
     499            CALL agrif_interp_lim3( 'V' ) 
     500#endif 
    488501#if defined key_bdy 
    489502         CALL bdy_ice_lim_dyn( 'V' ) 
     
    513526            CALL agrif_rhg_lim2( jter, nn_nevp, 'V' ) 
    514527#endif 
     528#if defined key_agrif && defined key_lim3 
     529            CALL agrif_interp_lim3( 'V' ) 
     530#endif 
    515531#if defined key_bdy 
    516532         CALL bdy_ice_lim_dyn( 'V' ) 
     
    537553#if defined key_agrif && defined key_lim2 
    538554            CALL agrif_rhg_lim2( jter, nn_nevp, 'U' ) 
     555#endif 
     556#if defined key_agrif && defined key_lim3 
     557            CALL agrif_interp_lim3( 'U' ) 
    539558#endif 
    540559#if defined key_bdy 
     
    576595      CALL agrif_rhg_lim2( nn_nevp , nn_nevp, 'U' ) 
    577596      CALL agrif_rhg_lim2( nn_nevp , nn_nevp, 'V' ) 
     597#endif 
     598#if defined key_agrif && defined key_lim3 
     599      CALL agrif_interp_lim3( 'U' ) 
     600      CALL agrif_interp_lim3( 'V' ) 
    578601#endif 
    579602#if defined key_bdy 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limtrp.F90

    r6515 r6584  
    102102      ENDIF 
    103103       
     104      CALL lim_var_agg( 1 ) ! integrated values + ato_i 
     105 
    104106      !-------------------------------------! 
    105107      !   Advection of sea ice properties   ! 
     
    113115      zvsold = v_s 
    114116      zsmvold(:,:) = SUM( smv_i(:,:,:), dim=3 ) 
    115       zeiold (:,:) = SUM( SUM( e_i(:,:,1:nlay_i,:), dim=4 ), dim=3 )  
    116       zesold (:,:) = SUM( SUM( e_s(:,:,1:nlay_s,:), dim=4 ), dim=3 )  
     117      zeiold (:,:) = et_i 
     118      zesold (:,:) = et_s  
    117119 
    118120      !--- Thickness correction init. --- ! 
    119       zatold(:,:) = SUM( a_i(:,:,:), dim=3 ) 
     121      zatold(:,:) = at_i 
    120122      DO jl = 1, jpl 
    121123         DO jj = 1, jpj 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limvar.F90

    r6515 r6584  
    8989      vt_s (:,:) = SUM( v_s, dim=3 ) 
    9090      at_i (:,:) = SUM( a_i, dim=3 ) 
     91      et_s(:,:)  = SUM( SUM( e_s(:,:,:,:), dim=4 ), dim=3 ) 
     92      et_i(:,:)  = SUM( SUM( e_i(:,:,:,:), dim=4 ), dim=3 ) 
    9193 
    9294      ! open water fraction 
     
    98100 
    99101      IF( kn > 1 ) THEN 
    100          et_s(:,:)  = SUM( SUM( e_s(:,:,:,:), dim=4 ), dim=3 )  ! snow heat content 
    101          et_i(:,:)  = SUM( SUM( e_i(:,:,:,:), dim=4 ), dim=3 )  ! ice  heat content 
    102102 
    103103         ! mean ice/snow thickness 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/NST_SRC/agrif_ice.F90

    r3680 r6584  
    55   !!---------------------------------------------------------------------- 
    66   !! History :  3.4  ! 2012-08  (R. Benshila)  Original code 
     7   !!            3.6  ! 2016-05  (C. Rousset)   Add LIM3 compatibility 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_agrif && defined key_lim2 
     
    6061 
    6162#endif 
     63 
     64#if defined key_agrif && defined key_lim3 
     65   !!---------------------------------------------------------------------- 
     66   !!   'key_agrif'                                              AGRIF zoom 
     67   !!----------------------------------------------------------------------    
     68   IMPLICIT NONE 
     69   PRIVATE  
     70 
     71   INTEGER, PUBLIC ::  u_ice_id, v_ice_id, tra_ice_id 
     72   INTEGER, PUBLIC ::  lim_nbstep = 0    ! child time position in sea-ice model 
     73 
     74   !!---------------------------------------------------------------------- 
     75   !! NEMO/NST 3.6 , NEMO Consortium (2016) 
     76   !! $Id$ 
     77   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     78   !!---------------------------------------------------------------------- 
     79 
     80#endif 
    6281   !!====================================================================== 
    6382END MODULE agrif_ice 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/NST_SRC/agrif_user.F90

    r6204 r6584  
    554554#  endif 
    555555 
     556#if defined key_lim3 
     557SUBROUTINE Agrif_InitValues_cont_lim3 
     558   !!---------------------------------------------------------------------- 
     559   !!                 *** ROUTINE Agrif_InitValues_cont_lim3 *** 
     560   !! 
     561   !! ** Purpose :: Initialisation of variables to be interpolated for LIM3 
     562   !!---------------------------------------------------------------------- 
     563   USE Agrif_Util 
     564   USE ice 
     565   USE agrif_ice 
     566   USE in_out_manager 
     567   USE agrif_lim3_update 
     568   USE agrif_lim3_interp 
     569   USE lib_mpp 
     570   ! 
     571   IMPLICIT NONE 
     572   !!---------------------------------------------------------------------- 
     573   ! 
     574   ! Declaration of the type of variable which have to be interpolated (parent=>child) 
     575   !---------------------------------------------------------------------------------- 
     576   CALL agrif_declare_var_lim3 
     577 
     578   ! clem: reset nn_fsbc(child) to rhot if rhot * nn_fsbc(parent) /= N * nn_fsbc(child) with N being integer 
     579   IF( MOD( Agrif_irhot() * Agrif_Parent(nn_fsbc), nn_fsbc ) /= 0 )  THEN 
     580      nn_fsbc = Agrif_irhot() 
     581      CALL ctl_warn ('rhot * nn_fsbc(parent) /= N * nn_fsbc(child), therefore nn_fsbc(child) is set to rhot') 
     582      WRITE(*,*) 'New nn_fsbc(child) = ', nn_fsbc 
     583   ENDIF 
     584 
     585   ! clem: reset update frequency if different from nn_fsbc 
     586   IF( nbclineupdate /= nn_fsbc ) THEN 
     587      nbclineupdate = nn_fsbc 
     588      CALL ctl_warn ('With ice model on child grid, nc_cln_update is set to nn_fsbc') 
     589   ENDIF 
     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   ! 
     603END SUBROUTINE Agrif_InitValues_cont_lim3 
     604 
     605SUBROUTINE agrif_declare_var_lim3 
     606   !!---------------------------------------------------------------------- 
     607   !!                 *** ROUTINE agrif_declare_var_lim3 *** 
     608   !! 
     609   !! ** Purpose :: Declaration of variables to be interpolated for LIM3 
     610   !!---------------------------------------------------------------------- 
     611   USE agrif_util 
     612   USE ice 
     613 
     614   IMPLICIT NONE 
     615   !!---------------------------------------------------------------------- 
     616   ! 
     617   ! 1. Declaration of the type of variable which have to be interpolated (parent=>child) 
     618   !       agrif_declare_variable(position,1st point index,--,--,dimensions,name) 
     619   !------------------------------------------------------------------------------------- 
     620   CALL agrif_declare_variable((/2,2,0,0/),(/3,3,0,0/),(/'x','y','N','N'/),(/1,1,1,1/), & 
     621      &                        (/jpi,jpj,jpl,jpl*(5+nlay_s+nlay_i)/), tra_ice_id ) 
     622   CALL agrif_declare_variable((/1,2/)    ,(/2,3/)    ,(/'x','y'/)        ,(/1,1/)    ,(/jpi,jpj/)      ,u_ice_id  ) 
     623   CALL agrif_declare_variable((/2,1/)    ,(/3,2/)    ,(/'x','y'/)        ,(/1,1/)    ,(/jpi,jpj/)      ,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 
     645 
    556646 
    557647# if defined key_top 
     
    720810   !!---------------------------------------------------------------------- 
    721811   !!                     *** ROUTINE agrif_init *** 
     812   !!   Read by Child model only 
    722813   !!---------------------------------------------------------------------- 
    723814   USE agrif_oce  
     
    766857   IF( agrif_oce_alloc()  > 0 )   CALL ctl_warn('agrif agrif_oce_alloc: allocation of arrays failed') 
    767858# if defined key_lim2 
    768    IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') 
     859   IF( agrif_ice_alloc()  > 0 )   CALL ctl_stop('agrif agrif_ice_alloc: allocation of arrays failed') ! only for LIM2 (not LIM3) 
    769860# endif 
    770861   ! 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r6399 r6584  
    15671567 
    15681568      ! --- heat flux associated with emp (W/m2) --- ! 
    1569       zqemp_oce(:,:) = -      zevap(:,:)                   * p_frld(:,:)      *   zcptn(:,:)   &      ! evap 
    1570          &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptn(:,:)   &      ! liquid precip 
    1571          &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptn(:,:) - lfus ) ! solid precip over ocean 
     1569      zqemp_oce(:,:) = -      zevap(:,:)                   * p_frld(:,:)      *   zcptn(:,:)   &       ! evap 
     1570         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptn(:,:)   &       ! liquid precip 
     1571         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptn(:,:) - lfus )  ! solid precip over ocean + snow melting 
    15721572!      zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptn(:,:)   &      ! ice evap 
    15731573!         &             +   zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice 
    15741574      zqemp_ice(:,:) =      zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice (only) 
    1575                                                                                                        ! qevap_ice=0 since we consider Tice=0°C 
     1575                                                                                                       ! qevap_ice=0 since we consider Tice=0degC 
    15761576       
    1577       ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
     1577      ! --- enthalpy of snow precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    15781578      zqprec_ice(:,:) = rhosn * ( zcptn(:,:) - lfus ) 
    15791579 
    15801580      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- ! 
    15811581      DO jl = 1, jpl 
    1582          zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but we do not have Tice, so we consider Tice=0°C 
     1582         zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but we do not have Tice, so we consider Tice=0degC 
    15831583      END DO 
    15841584 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_lim.F90

    r6515 r6584  
    6666   USE bdyice_lim       ! unstructured open boundary data  (bdy_ice_lim routine) 
    6767#endif 
     68# if defined key_agrif 
     69   USE agrif_ice 
     70   USE agrif_lim3_update 
     71   USE agrif_lim3_interp 
     72# endif 
    6873 
    6974   IMPLICIT NONE 
     
    119124      !-----------------------! 
    120125      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
     126 
     127# if defined key_agrif 
     128         IF( .NOT. Agrif_Root() ) THEN 
     129            lim_nbstep = MOD( lim_nbstep, Agrif_irhot() * Agrif_Parent(nn_fsbc) / nn_fsbc ) + 1 
     130         ENDIF 
     131# endif 
    121132 
    122133         ! mean surface ocean current at ice velocity point (C-grid dynamics :  U- & V-points as the ocean) 
     
    162173                                      CALL lim_rst_opn( kt )   ! Open Ice restart file 
    163174         ! 
     175#if defined key_agrif 
     176          IF( .NOT. Agrif_Root() )    CALL agrif_interp_lim3('T') 
     177#endif 
    164178         ! --- zap this if no ice dynamics --- ! 
    165179         IF( .NOT. lk_c1d .AND. ln_limdyn ) THEN 
     
    178192         ENDIF 
    179193         ! --- 
     194#if defined key_agrif 
     195          IF( .NOT. Agrif_Root() )    CALL agrif_interp_lim3('T') 
     196#endif 
    180197#if defined key_bdy 
    181          IF( ln_limthd )              CALL bdy_ice_lim( kt )   ! bdy ice thermo  
     198         IF( ln_limthd )              CALL bdy_ice_lim( kt )   ! -- bdy ice thermo  
    182199         IF( ln_icectl )              CALL lim_prt( kt, iiceprt, jiceprt, 1, ' - ice thermo bdy - ' ) 
    183200#endif 
     
    237254         IF( ln_limthd )              CALL lim_update2( kt )    ! -- Corrections 
    238255         ! --- 
     256# if defined key_agrif 
     257         IF( .NOT. Agrif_Root() )     CALL agrif_update_lim3( kt ) 
     258# endif 
    239259                                      CALL lim_var_glo2eqv      ! necessary calls (at least for coupling) 
    240260                                      CALL lim_var_agg( 2 )     ! necessary calls (at least for coupling) 
     
    345365      ! 
    346366      IF( nstock == 0 )   nstock = nlast + 1 
     367      ! 
     368# if defined key_agrif 
     369      IF( .NOT. Agrif_Root() )   CALL Agrif_InitValues_cont_lim3 
     370# endif 
    347371      ! 
    348372   END SUBROUTINE sbc_lim_init 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6204 r6584  
    133133# endif 
    134134# if defined key_lim2 
    135       CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM 
     135      CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM2 
     136# endif 
     137# if defined key_lim3 
     138      CALL Agrif_Declare_Var_lim3  !  "      "   "   "      "  LIM3 
    136139# endif 
    137140#endif 
  • branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/SAS_SRC/nemogcm.F90

    r6204 r6584  
    111111# endif 
    112112# if defined key_lim2 
    113       CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM 
     113      CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM2 
     114# endif 
     115# if defined key_lim3 
     116      CALL Agrif_Declare_Var_lim3  !  "      "   "   "      "  LIM3 
    114117# endif 
    115118#endif 
Note: See TracChangeset for help on using the changeset viewer.