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 5123 for trunk/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90 – NEMO

Ignore:
Timestamp:
2015-03-04T17:06:03+01:00 (9 years ago)
Author:
clem
Message:

major LIM3 cleaning + monocat capabilities + NEMO namelist-consistency; sette to follow

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r5020 r5123  
    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 
    4544 
    4645   IMPLICIT NONE 
    4746   PRIVATE 
    4847 
    49    PUBLIC   lim_sbc_init   ! called by ice_init 
     48   PUBLIC   lim_sbc_init   ! called by sbc_lim_init 
    5049   PUBLIC   lim_sbc_flx    ! called by sbc_ice_lim 
    5150   PUBLIC   lim_sbc_tau    ! called by sbc_ice_lim 
     
    9998      !!              Tartinville et al. 2001 Ocean Modelling, 3, 95-108. 
    10099      !!              These refs are now obsolete since everything has been revised 
    101       !!              The ref should be Rousset et al., 2015? 
     100      !!              The ref should be Rousset et al., 2015 
    102101      !!--------------------------------------------------------------------- 
    103102      INTEGER, INTENT(in) ::   kt                                   ! number of iteration 
    104       ! 
    105103      INTEGER  ::   ji, jj, jl, jk                                  ! dummy loop indices 
    106       ! 
    107       REAL(wp) ::   zemp                                            !  local scalars 
     104      REAL(wp) ::   zemp                                            ! local scalars 
    108105      REAL(wp) ::   zf_mass                                         ! Heat flux associated with mass exchange ice->ocean (W.m-2) 
    109106      REAL(wp) ::   zfcm1                                           ! New solar flux received by the ocean 
     
    172169               zemp =   emp(ji,jj)     *           pfrld(ji,jj)            &   ! evaporation over oceanic fraction 
    173170                  &   - 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 
     171                  &   + sprecip(ji,jj) * ( 1._wp - pfrld(ji,jj)**rn_betas )       ! except solid precip intercepted by sea-ice 
    175172            ENDIF 
    176173 
     
    199196         snwice_mass_b(:,:) = snwice_mass(:,:)                   
    200197         ! new mass per unit area 
    201          snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
     198         snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
    202199         ! time evolution of snow+ice mass 
    203200         snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) * r1_rdtice 
     
    225222      ENDIF 
    226223 
     224      IF( ln_nicep )   CALL lim_prt( kt, jiindx, jjindx, 3, ' - Final state lim_sbc - ' )   ! control print 
    227225 
    228226      IF(ln_ctl) THEN 
     
    270268      ! 
    271269      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN     !==  Ice time-step only  ==!   (i.e. surface module time-step) 
    272 !CDIR NOVERRCHK 
    273270         DO jj = 2, jpjm1                             !* update the modulus of stress at ocean surface (T-point) 
    274 !CDIR NOVERRCHK 
    275271            DO ji = fs_2, fs_jpim1 
    276272               !                                               ! 2*(U_ice-U_oce) at T-point 
     
    322318      !! ** input   : Namelist namicedia 
    323319      !!------------------------------------------------------------------- 
    324       REAL(wp) :: zsum, zarea 
    325       ! 
    326320      INTEGER  ::   ji, jj, jk                       ! dummy loop indices 
    327321      REAL(wp) ::   zcoefu, zcoefv, zcoeff          ! local scalar 
     
    343337         END WHERE 
    344338      ENDIF 
    345       ! clem modif 
     339       
    346340      IF( .NOT. ln_rstart ) THEN 
    347341         fraqsr_1lev(:,:) = 1._wp 
    348342      ENDIF 
    349343      ! 
    350       ! clem: snwice_mass in the restart file now 
    351344      IF( .NOT. ln_rstart ) THEN 
    352345         !                                      ! embedded sea ice 
    353346         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(:,:)  ) 
     347            snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  ) 
    355348            snwice_mass_b(:,:) = snwice_mass(:,:) 
    356349         ELSE 
Note: See TracChangeset for help on using the changeset viewer.