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 3402 for branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90 – NEMO

Ignore:
Timestamp:
2012-05-25T18:43:49+02:00 (12 years ago)
Author:
acc
Message:

Branch: dev_r3385_NOCS04_HAMF; #665. Stage 2 of 2012 development: suppression of emps array and introduction of sfx (salt flux) array with associated code to setup the options for embedding the seaice into the ocean

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_2/limsbc_2.F90

    r3396 r3402  
    3939   USE prtctl           ! Print control 
    4040   USE cpl_oasis3, ONLY : lk_cpl 
     41   USE oce, ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass  
    4142 
    4243   IMPLICIT NONE 
     
    9293      !!              - qns     : sea heat flux    : non solar (including heat content of the mass flux) 
    9394      !!              - emp     : freshwater budget: mass flux  
    94       !!              - emps    : freshwater budget: salt flux due to Freezing/Melting 
     95      !!              - sfx     : freshwater budget: salt flux due to Freezing/Melting 
    9596      !!              - utau    : sea surface i-stress (ocean referential) 
    9697      !!              - vtau    : sea surface j-stress (ocean referential) 
     
    119120      CALL wrk_alloc( jpi, jpj, 1, zalb, zalbp ) 
    120121 
    121       zswitch = 1                                ! Default standard levitating sea-ice (salt exchanges only) 
    122 !!gm ice embedment 
    123 !     SELECT CASE( nn_ice_embd )                 ! levitating/embedded sea-ice option (not yet activated) 
    124 !       CASE( 0    )   ;   zswitch = 1           ! standard levitating sea-ice : salt exchange only 
    125 !       CASE( 1, 2 )   ;   zswitch = 0           ! other levitating sea-ice or embedded sea-ice : salt and volume fluxes 
    126 !     END SELECT                                 !     
    127 !!gm end embedment 
     122      SELECT CASE( nn_ice_embd )                 ! levitating or embedded sea-ice option 
     123        CASE( 0    )   ;   zswitch = 1           ! (0) standard levitating sea-ice : salt exchange only 
     124        CASE( 1, 2 )   ;   zswitch = 0           ! (1) levitating sea-ice: salt and volume exchange but no pressure effect 
     125                                                 ! (2) embedded sea-ice : salt and volume fluxes and pressure 
     126      END SELECT                                 !     
     127 
    128128      !------------------------------------------! 
    129129      !      heat flux at the ocean surface      ! 
     
    147147!!$            i1mfr   = 1.0 - AINT(  frld(ji,jj) )                   ! = 0. if ice-free ocean else 1. (after ice thermo) 
    148148!!$ 
    149 !!$            IF( phicif(ji,jj) <= 0. ) THEN   ;   ifvt = zinda      ! = 1. if there was snow and ice before the ice thermo. which has been completely melted (possibly overmelted) 
     149!!$            IF( phicif(ji,jj) <= 0. ) THEN   ;   ifvt = zinda      ! = zinda if previous thermodynamic step overmelted the ice??? 
    150150!!$            ELSE                             ;   ifvt = 0.         !  
    151151!!$            ENDIF 
     
    222222            ! salt flux only       : add concentration dilution term in salt flux  and no  F-M term in volume flux 
    223223            ! salt and mass fluxes : non concentartion dilution term in salt flux  and add F-M term in volume flux 
    224             emps(ji,jj) = zfsalt +                  zswitch  * zcd   ! salt flux (+ C/D if no ice/ocean mass exchange) 
     224            sfx (ji,jj) = zfsalt +                  zswitch  * zcd   ! salt flux (+ C/D if no ice/ocean mass exchange) 
    225225            emp (ji,jj) = zemp   + zemp_snw + ( 1.- zswitch) * zfmm  ! mass flux (- F/M mass flux if no ice/ocean mass exchange) 
    226226            ! 
    227227         END DO 
    228228      END DO 
     229      !                                !------------------------------------------! 
     230      !                                !    mass of snow and ice per unit area    ! 
     231      !                                !------------------------------------------! 
     232      IF( nn_ice_embd /= 0 ) THEN      ! embedded sea-ice (mass required) 
     233         snwice_mass_b(:,:) = snwice_mass(:,:)                  ! save mass from the previous ice time step 
     234         !                                                      ! new mass per unit area 
     235         snwice_mass  (:,:) = tms(:,:) * ( rhosn * hsnif(:,:) + rhoic * hicif(:,:)  ) * ( 1.0 - frld(:,:) ) 
     236         !                                                      ! time evolution of snow+ice mass 
     237         snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) / rdt_ice 
     238      ENDIF 
    229239 
    230240      CALL iom_put( 'hflx_ice_cea', - fdtcn(:,:) )       
     
    255265      IF(ln_ctl) THEN            ! control print 
    256266         CALL prt_ctl(tab2d_1=qsr   , clinfo1=' lim_sbc: qsr    : ', tab2d_2=qns   , clinfo2=' qns     : ') 
    257          CALL prt_ctl(tab2d_1=emp   , clinfo1=' lim_sbc: emp    : ', tab2d_2=emps  , clinfo2=' emps    : ') 
     267         CALL prt_ctl(tab2d_1=emp   , clinfo1=' lim_sbc: emp    : ', tab2d_2=sfx   , clinfo2=' sfx     : ') 
    258268         CALL prt_ctl(tab2d_1=utau  , clinfo1=' lim_sbc: utau   : ', mask1=umask,   & 
    259269            &         tab2d_2=vtau  , clinfo2=' vtau    : '        , mask2=vmask ) 
     
    451461         END WHERE 
    452462      ENDIF 
     463      !                                      ! embedded sea ice 
     464      IF( nn_ice_embd /= 0 ) THEN            ! mass exchanges between ice and ocean (case 1 or 2) set the snow+ice mass 
     465         snwice_mass  (:,:) = tms(:,:) * ( rhosn * hsnif(:,:) + rhoic * hicif(:,:)  ) * ( 1.0 - frld(:,:) ) 
     466         snwice_mass_b(:,:) = snwice_mass(:,:) 
     467      ELSE 
     468         snwice_mass  (:,:) = 0.e0           ! no mass exchanges 
     469         snwice_mass_b(:,:) = 0.e0           ! no mass exchanges 
     470      ENDIF 
     471      IF( nn_ice_embd == 2 .AND.          &  ! full embedment (case 2) & no restart :  
     472         &   .NOT.ln_rstart ) THEN           ! deplete the initial ssh belew sea-ice area 
     473         sshn(:,:) = sshn(:,:) - snwice_mass(:,:) * r1_rau0 
     474         sshb(:,:) = sshb(:,:) - snwice_mass(:,:) * r1_rau0 
     475      ENDIF 
    453476      ! 
    454477   END SUBROUTINE lim_sbc_init_2 
Note: See TracChangeset for help on using the changeset viewer.