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 5313 for branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90 – NEMO

Ignore:
Timestamp:
2015-05-29T11:46:03+02:00 (9 years ago)
Author:
timgraham
Message:

Merged head of trunk (r5302) into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r5312 r5313  
    2525   USE par_oce          ! ocean parameters 
    2626   USE phycst           ! physical constants 
    27    USE par_ice          ! ice parameters 
    2827   USE dom_oce          ! ocean domain 
    29    USE dom_ice,    ONLY : tms, area 
    3028   USE ice              ! LIM sea-ice variables 
    3129   USE sbc_ice          ! Surface boundary condition: sea-ice fields 
     
    4038   USE prtctl           ! Print control 
    4139   USE lib_fortran      ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    42    USE traqsr           ! clem: add penetration of solar flux into the calculation of heat budget 
     40   USE traqsr           ! add penetration of solar flux in the calculation of heat budget 
    4341   USE iom 
    4442   USE domvvl           ! Variable volume 
     43   USE limctl 
     44   USE limcons 
    4545 
    4646   IMPLICIT NONE 
    4747   PRIVATE 
    4848 
    49    PUBLIC   lim_sbc_init   ! called by ice_init 
     49   PUBLIC   lim_sbc_init   ! called by sbc_lim_init 
    5050   PUBLIC   lim_sbc_flx    ! called by sbc_ice_lim 
    5151   PUBLIC   lim_sbc_tau    ! called by sbc_ice_lim 
     
    9999      !!              Tartinville et al. 2001 Ocean Modelling, 3, 95-108. 
    100100      !!              These refs are now obsolete since everything has been revised 
    101       !!              The ref should be Rousset et al., 2015? 
     101      !!              The ref should be Rousset et al., 2015 
    102102      !!--------------------------------------------------------------------- 
    103103      INTEGER, INTENT(in) ::   kt                                   ! number of iteration 
    104       ! 
    105104      INTEGER  ::   ji, jj, jl, jk                                  ! dummy loop indices 
    106       ! 
    107       REAL(wp) ::   zemp                                            !  local scalars 
     105      REAL(wp) ::   zemp                                            ! local scalars 
    108106      REAL(wp) ::   zf_mass                                         ! Heat flux associated with mass exchange ice->ocean (W.m-2) 
    109107      REAL(wp) ::   zfcm1                                           ! New solar flux received by the ocean 
     
    149147            hfx_out(ji,jj) = hfx_out(ji,jj) + zf_mass + zfcm1 
    150148 
     149            ! Add the residual from heat diffusion equation (W.m-2) 
     150            !------------------------------------------------------- 
     151            hfx_out(ji,jj) = hfx_out(ji,jj) + hfx_err_dif(ji,jj) 
     152 
    151153            ! New qsr and qns used to compute the oceanic heat flux at the next time step 
    152154            !--------------------------------------------------- 
     
    167169            !  computing freshwater exchanges at the ice/ocean interface 
    168170            IF( lk_cpl ) THEN  
    169                zemp = - emp_tot(ji,jj) + emp_ice(ji,jj) * ( 1. - pfrld(ji,jj) )    &   ! 
    170                   &   + wfx_snw(ji,jj) 
     171                zemp =   emp_tot(ji,jj)                                    &   ! net mass flux over grid cell 
     172                   &   - emp_ice(ji,jj) * ( 1._wp - pfrld(ji,jj) )         &   ! minus the mass flux intercepted by sea ice 
     173                   &   + sprecip(ji,jj) * ( pfrld(ji,jj) - pfrld(ji,jj)**rn_betas )   ! 
    171174            ELSE 
    172175               zemp =   emp(ji,jj)     *           pfrld(ji,jj)            &   ! evaporation over oceanic fraction 
    173176                  &   - tprecip(ji,jj) * ( 1._wp - pfrld(ji,jj) )          &   ! all precipitation reach the ocean 
    174                   &   + sprecip(ji,jj) * ( 1._wp - pfrld(ji,jj)**betas )       ! except solid precip intercepted by sea-ice 
     177                  &   + sprecip(ji,jj) * ( 1._wp - pfrld(ji,jj)**rn_betas )       ! except solid precip intercepted by sea-ice 
    175178            ENDIF 
    176179 
     
    180183 
    181184            ! mass flux at the ocean/ice interface 
    182             fmmflx(ji,jj) = - wfx_ice(ji,jj) * r1_rdtice                    ! F/M mass flux save at least for biogeochemical model 
    183             emp(ji,jj)    = zemp - wfx_ice(ji,jj) - wfx_snw(ji,jj)       ! mass flux + F/M mass flux (always ice/ocean mass exchange) 
     185            fmmflx(ji,jj) = - ( wfx_ice(ji,jj) + wfx_snw(ji,jj) ) * r1_rdtice  ! F/M mass flux save at least for biogeochemical model 
     186            emp(ji,jj)    = zemp - wfx_ice(ji,jj) - wfx_snw(ji,jj)             ! mass flux + F/M mass flux (always ice/ocean mass exchange) 
    184187             
    185188         END DO 
     
    199202         snwice_mass_b(:,:) = snwice_mass(:,:)                   
    200203         ! new mass per unit area 
    201          snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
     204         snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
    202205         ! time evolution of snow+ice mass 
    203206         snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) * r1_rdtice 
     
    225228      ENDIF 
    226229 
     230      ! conservation test 
     231      IF( ln_limdiahsb ) CALL lim_cons_final( 'limsbc' ) 
     232 
     233      ! control prints 
     234      IF( ln_icectl )   CALL lim_prt( kt, iiceprt, jiceprt, 3, ' - Final state lim_sbc - ' ) 
    227235 
    228236      IF(ln_ctl) THEN 
     
    270278      ! 
    271279      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !==  Ice time-step only  ==!   (i.e. surface module time-step) 
    272 !CDIR NOVERRCHK 
    273280         DO jj = 2, jpjm1                             !* update the modulus of stress at ocean surface (T-point) 
    274 !CDIR NOVERRCHK 
    275281            DO ji = fs_2, fs_jpim1 
    276282               !                                               ! 2*(U_ice-U_oce) at T-point 
     
    322328      !! ** input   : Namelist namicedia 
    323329      !!------------------------------------------------------------------- 
    324       REAL(wp) :: zsum, zarea 
    325       ! 
    326330      INTEGER  ::   ji, jj, jk                       ! dummy loop indices 
    327331      REAL(wp) ::   zcoefu, zcoefv, zcoeff          ! local scalar 
     
    343347         END WHERE 
    344348      ENDIF 
    345       ! clem modif 
     349       
    346350      IF( .NOT. ln_rstart ) THEN 
    347351         fraqsr_1lev(:,:) = 1._wp 
    348352      ENDIF 
    349353      ! 
    350       ! clem: snwice_mass in the restart file now 
    351354      IF( .NOT. ln_rstart ) THEN 
    352355         !                                      ! embedded sea ice 
    353356         IF( nn_ice_embd /= 0 ) THEN            ! mass exchanges between ice and ocean (case 1 or 2) set the snow+ice mass 
    354             snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  ) 
     357            snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  ) 
    355358            snwice_mass_b(:,:) = snwice_mass(:,:) 
    356359         ELSE 
Note: See TracChangeset for help on using the changeset viewer.