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

Changeset 9780


Ignore:
Timestamp:
2018-06-12T14:12:51+02:00 (6 years ago)
Author:
jchanut
Message:

Reorganize Agrif update in a single subroutine ; use adjoint stepping for initial state update

Location:
NEMO/trunk/src
Files:
1 added
6 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/NST/agrif_ice_update.F90

    r9761 r9780  
    4242CONTAINS 
    4343 
    44    SUBROUTINE agrif_update_ice( kt ) 
     44   SUBROUTINE agrif_update_ice( ) 
    4545      !!---------------------------------------------------------------------- 
    4646      !!                     *** ROUTINE agrif_update_ice *** 
     
    4949      !! ** Action : - Update (u_ice,v_ice) and ice tracers 
    5050      !!---------------------------------------------------------------------- 
    51       INTEGER, INTENT(in) :: kt 
    52       !!---------------------------------------------------------------------- 
    5351      ! 
    5452      IF( Agrif_Root() .OR. nn_ice == 0 ) RETURN   ! do not update if inside Parent Grid or if child domain does not have ice 
    5553      ! 
    56       IF( ( MOD( (kt-nit000)/nn_fsbc + 1, Agrif_irhot() * Agrif_Parent(nn_fsbc)/nn_fsbc ) /=0 ) .AND. (kt /= 0) ) RETURN   ! update only at the parent ice time step 
     54      IF (lwp.AND.lk_agrif_debug) Write(*,*) 'Update sea ice from grid Number',Agrif_Fixed() 
     55      ! 
     56!      IF( ( MOD( (kt-nit000)/nn_fsbc + 1, Agrif_irhot() * Agrif_Parent(nn_fsbc)/nn_fsbc ) /=0 ) .AND. (kt /= 0) ) RETURN   ! update only at the parent ice time step 
    5757      ! 
    5858      Agrif_SpecialValueFineGrid    = -9999. 
  • NEMO/trunk/src/NST/agrif_oce_update.F90

    r9758 r9780  
    144144      Agrif_UseSpecialValueInUpdate = .FALSE. 
    145145      ! 
    146 #  if defined DECAL_FEEDBACK && defined VOL_REFLUX 
     146#  if defined VOL_REFLUX 
    147147      IF ( ln_dynspg_ts.AND.ln_bt_fw ) THEN 
    148148         ! Refluxing on ssh: 
     149#  if defined DECAL_FEEDBACK 
    149150         CALL Agrif_Update_Variable(ub2b_update_id,locupdate1=(/0, 0/),locupdate2=(/1, 1/),procname = reflux_sshu) 
    150151         CALL Agrif_Update_Variable(vb2b_update_id,locupdate1=(/1, 1/),locupdate2=(/0, 0/),procname = reflux_sshv) 
     152#  else 
     153         CALL Agrif_Update_Variable(ub2b_update_id,locupdate1=(/-1,-1/),locupdate2=(/ 0, 0/),procname = reflux_sshu) 
     154         CALL Agrif_Update_Variable(vb2b_update_id,locupdate1=(/ 0, 0/),locupdate2=(/-1,-1/),procname = reflux_sshv) 
     155#  endif 
    151156      END IF 
    152157#  endif 
     
    157162 
    158163 
    159    SUBROUTINE Agrif_Update_Tke( kt ) 
     164   SUBROUTINE Agrif_Update_Tke( ) 
    160165      !!--------------------------------------------- 
    161166      !!   *** ROUTINE Agrif_Update_Tke *** 
    162167      !!--------------------------------------------- 
    163168      !! 
    164       INTEGER, INTENT(in) :: kt  
    165169      !  
    166170      IF (Agrif_Root()) RETURN 
    167171      !        
    168       IF( ( Agrif_NbStepint() .NE. 0 ) .AND. (kt /= 0) ) RETURN 
    169172#  if defined TWO_WAY 
    170173 
  • NEMO/trunk/src/NST/agrif_user.F90

    r9761 r9780  
    6464   CALL Agrif_InitValues_cont_ice 
    6565# endif 
    66    ! 
    67    IF ( Agrif_Level().EQ.Agrif_MaxLevel() ) CALL agrif_Update_ini() 
    68  
    69    Agrif_UseSpecialValueInUpdate = .FALSE.      
    70  
     66   !     
    7167END SUBROUTINE Agrif_initvalues 
    7268 
     
    296292END SUBROUTINE Agrif_InitValues_cont 
    297293 
    298 RECURSIVE SUBROUTINE Agrif_Update_ini( ) 
    299    !!---------------------------------------------------------------------- 
    300    !!                 *** ROUTINE agrif_Update_ini *** 
    301    !! 
    302    !! ** Purpose :: Recursive update done at initialization 
    303    !!---------------------------------------------------------------------- 
    304    USE dom_oce 
    305    USE agrif_oce_update 
    306 #if defined key_top 
    307    USE agrif_top_update 
    308 #endif 
    309 #if defined key_si3 
    310    USE agrif_ice_update 
    311 #endif 
    312    ! 
    313    IMPLICIT NONE 
    314    !!---------------------------------------------------------------------- 
    315    ! 
    316    IF (Agrif_Root()) RETURN 
    317    ! 
    318    CALL Agrif_Update_ssh() 
    319    IF (.NOT.ln_linssh) CALL Agrif_Update_vvl() 
    320    CALL Agrif_Update_tra() 
    321 #if defined key_top 
    322    CALL Agrif_Update_Trc() 
    323 #endif 
    324    CALL Agrif_Update_dyn() 
    325 ! JC remove update because this precludes from perfect restartability 
    326 !!   CALL Agrif_Update_tke(0) 
    327  
    328 #if defined key_si3 
    329    CALL agrif_update_ice(0) 
    330 #endif 
    331     
    332    CALL Agrif_ChildGrid_To_ParentGrid() 
    333    CALL Agrif_Update_ini() 
    334    CALL Agrif_ParentGrid_To_ChildGrid() 
    335  
    336 END SUBROUTINE agrif_update_ini 
    337  
    338294SUBROUTINE agrif_declare_var 
    339295   !!---------------------------------------------------------------------- 
  • NEMO/trunk/src/OCE/nemogcm.F90

    r9656 r9780  
    8989   USE xios           ! xIOserver 
    9090#endif 
     91#if defined key_agrif 
     92   USE agrif_all_update   ! Master Agrif update 
     93#endif 
    9194 
    9295   IMPLICIT NONE 
     
    160163      !                                               !==  AGRIF time-stepping  ==! 
    161164      CALL Agrif_Regrid() 
     165      ! 
     166      ! Recursive update from highest nested level to lowest: 
     167      CALL Agrif_step_child_adj(Agrif_Update_All) 
    162168      ! 
    163169      DO WHILE( istp <= nitend .AND. nstop == 0 ) 
  • NEMO/trunk/src/OCE/step.F90

    r9610 r9780  
    294294                         CALL Agrif_Integrate_ChildGrids( stp )  ! allows to finish all the Child Grids before updating 
    295295 
    296       IF( Agrif_NbStepint() == 0 ) THEN               ! AGRIF Update from zoom N to zoom 1 then to Parent  
    297 !!jc in fact update is useless at last time step, but do it for global diagnostics 
    298 #if defined key_si3 
    299                               CALL Agrif_Update_ice( kstp )   ! update sea-ice 
    300 #endif 
    301                               CALL Agrif_Update_ssh()          ! Update ssh 
    302          IF(.NOT.ln_linssh)   CALL Agrif_Update_vvl()          ! Update vertical scale factors   
    303                               CALL Agrif_Update_Tra()          ! Update active tracers 
    304                               CALL Agrif_Update_Dyn()          ! Update momentum 
    305 # if defined key_top 
    306                               CALL Agrif_Update_Trc()          ! Update passive tracers 
    307 # endif 
    308       ENDIF 
     296                         IF( Agrif_NbStepint() == 0 ) CALL Agrif_update_all( ) ! Update all components 
    309297#endif 
    310298      IF( ln_diaobs  )   CALL dia_obs      ( kstp )      ! obs-minus-model (assimilation) diagnostics (call after dynamics update) 
  • NEMO/trunk/src/OCE/step_oce.F90

    r9598 r9780  
    104104#if defined key_agrif 
    105105   USE agrif_oce_sponge ! Momemtum and tracers sponges 
    106    USE agrif_oce_update ! Update (2-way nesting) 
    107 #if defined key_si3 
    108    USE agrif_ice_update 
    109 #endif 
    110 #if defined key_top 
    111    USE agrif_top_update ! passive tracers update (2-way nesting) 
    112 #endif 
     106   USE agrif_all_update ! Main update driver 
    113107#endif 
    114108#if defined key_top 
Note: See TracChangeset for help on using the changeset viewer.