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 10922 for NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/SBC/sbcmod.F90 – NEMO

Ignore:
Timestamp:
2019-05-02T17:10:39+02:00 (5 years ago)
Author:
acc
Message:

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Convert IOM, LDF, OBS and SBC directories and compatibility changes elsewhere that these changes enforce. Changes pass SETTE and compare with original trunk results. Outstanding issues (currently with work-arounds) in DIU/step_diu.F90 and fld_bdy_interp within SBC/fldread.F90; proper soltions pending

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/SBC/sbcmod.F90

    r10499 r10922  
    7676CONTAINS 
    7777 
    78    SUBROUTINE sbc_init 
     78   SUBROUTINE sbc_init( Kbb, Kmm ) 
    7979      !!--------------------------------------------------------------------- 
    8080      !!                    ***  ROUTINE sbc_init *** 
     
    8888      !!              - nsbc: type of sbc 
    8989      !!---------------------------------------------------------------------- 
     90      INTEGER, INTENT(in) ::   Kbb, Kmm              ! ocean time level indices 
    9091      INTEGER ::   ios, icpt                         ! local integer 
    9192      LOGICAL ::   ll_purecpl, ll_opa, ll_not_nemo   ! local logical 
     
    323324      !                       !**  associated modules : initialization 
    324325      ! 
    325                           CALL sbc_ssm_init           ! Sea-surface mean fields initialization 
    326       ! 
    327       IF( ln_blk      )   CALL sbc_blk_init            ! bulk formulae initialization 
    328  
    329       IF( ln_ssr      )   CALL sbc_ssr_init            ! Sea-Surface Restoring initialization 
    330       ! 
    331       IF( ln_isf      )   CALL sbc_isf_init            ! Compute iceshelves 
    332       ! 
    333                           CALL sbc_rnf_init            ! Runof initialization 
    334       ! 
    335       IF( ln_apr_dyn )    CALL sbc_apr_init            ! Atmo Pressure Forcing initialization 
     326                          CALL sbc_ssm_init ( Kbb, Kmm ) ! Sea-surface mean fields initialization 
     327      ! 
     328      IF( ln_blk      )   CALL sbc_blk_init              ! bulk formulae initialization 
     329 
     330      IF( ln_ssr      )   CALL sbc_ssr_init              ! Sea-Surface Restoring initialization 
     331      ! 
     332      IF( ln_isf      )   CALL sbc_isf_init( Kmm )       ! Compute iceshelves 
     333      ! 
     334                          CALL sbc_rnf_init( Kmm )       ! Runof initialization 
     335      ! 
     336      IF( ln_apr_dyn )    CALL sbc_apr_init              ! Atmo Pressure Forcing initialization 
    336337      ! 
    337338#if defined key_si3 
     
    359360 
    360361 
    361    SUBROUTINE sbc( kt ) 
     362   SUBROUTINE sbc( kt, Kbb, Kmm ) 
    362363      !!--------------------------------------------------------------------- 
    363364      !!                    ***  ROUTINE sbc  *** 
     
    376377      !!---------------------------------------------------------------------- 
    377378      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     379      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
    378380      ! 
    379381      LOGICAL ::   ll_sas, ll_opa   ! local logical 
     
    411413      ll_opa = nn_components == jp_iam_opa 
    412414      ! 
    413       IF( .NOT.ll_sas )   CALL sbc_ssm ( kt )            ! mean ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
    414       IF( ln_wave     )   CALL sbc_wave( kt )            ! surface waves 
     415      IF( .NOT.ll_sas )   CALL sbc_ssm ( kt, Kbb, Kmm )  ! mean ocean sea surface variables (sst_m, sss_m, ssu_m, ssv_m) 
     416      IF( ln_wave     )   CALL sbc_wave( kt, Kmm )       ! surface waves 
    415417 
    416418      ! 
     
    419421      SELECT CASE( nsbc )                                ! Compute ocean surface boundary condition 
    420422      !                                                  ! (i.e. utau,vtau, qns, qsr, emp, sfx) 
    421       CASE( jp_usr   )     ;   CALL usrdef_sbc_oce( kt )                    ! user defined formulation  
    422       CASE( jp_flx     )   ;   CALL sbc_flx       ( kt )                    ! flux formulation 
     423      CASE( jp_usr   )     ;   CALL usrdef_sbc_oce( kt )                             ! user defined formulation  
     424      CASE( jp_flx     )   ;   CALL sbc_flx       ( kt )                             ! flux formulation 
    423425      CASE( jp_blk     ) 
    424          IF( ll_sas    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: SAS receiving fields from OPA 
    425                                CALL sbc_blk       ( kt )                    ! bulk formulation for the ocean 
     426         IF( ll_sas    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice, Kbb, Kmm )  ! OPA-SAS coupling: SAS receiving fields from OPA 
     427                               CALL sbc_blk       ( kt )                             ! bulk formulation for the ocean 
    426428                               ! 
    427       CASE( jp_purecpl )   ;   CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! pure coupled formulation 
     429      CASE( jp_purecpl )   ;   CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice, Kbb, Kmm )  ! pure coupled formulation 
    428430      CASE( jp_none    ) 
    429          IF( ll_opa    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! OPA-SAS coupling: OPA receiving fields from SAS 
     431         IF( ll_opa    )       CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice, Kbb, Kmm )  ! OPA-SAS coupling: OPA receiving fields from SAS 
    430432      END SELECT 
    431433      ! 
    432       IF( ln_mixcpl )          CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice )   ! forced-coupled mixed formulation after forcing 
    433       ! 
    434       IF ( ln_wave .AND. (ln_tauwoc .OR. ln_tauw) ) CALL sbc_wstress( )      ! Wind stress provided by waves  
     434      IF( ln_mixcpl )          CALL sbc_cpl_rcv   ( kt, nn_fsbc, nn_ice, Kbb, Kmm )  ! forced-coupled mixed formulation after forcing 
     435      ! 
     436      IF ( ln_wave .AND. (ln_tauwoc .OR. ln_tauw) ) CALL sbc_wstress( )              ! Wind stress provided by waves  
    435437      ! 
    436438      !                                            !==  Misc. Options  ==! 
    437439      ! 
    438440      SELECT CASE( nn_ice )                                       ! Update heat and freshwater fluxes over sea-ice areas 
    439       CASE(  1 )   ;         CALL sbc_ice_if   ( kt )             ! Ice-cover climatology ("Ice-if" model) 
     441      CASE(  1 )   ;         CALL sbc_ice_if   ( kt, Kbb, Kmm )   ! Ice-cover climatology ("Ice-if" model) 
    440442#if defined key_si3 
    441443      CASE(  2 )   ;         CALL ice_stp  ( kt, nsbc )           ! SI3 ice model 
     
    451453      ENDIF 
    452454 
    453       IF( ln_isf         )   CALL sbc_isf( kt )                   ! compute iceshelves 
     455      IF( ln_isf         )   CALL sbc_isf( kt, Kmm )              ! compute iceshelves 
    454456 
    455457      IF( ln_rnf         )   CALL sbc_rnf( kt )                   ! add runoffs to fresh water fluxes 
Note: See TracChangeset for help on using the changeset viewer.