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 3517 for branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90 – NEMO

Ignore:
Timestamp:
2012-10-26T12:13:21+02:00 (11 years ago)
Author:
gm
Message:

gm: Branch: dev_r3385_NOCS04_HAMF; #665. update sbccpl ; change LIM3 from equivalent salt flux to salt flux and mass flux

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r3488 r3517  
    99   !!            3.3  ! 2010-05 (G. Madec) decrease ocean & ice reference salinities in the Baltic sea 
    1010   !!                 !                  + simplification of the ice-ocean stress calculation 
    11    !!            4.0  ! 2011-02 (G. Madec) dynamical allocation 
     11   !!            3.4  ! 2011-02 (G. Madec) dynamical allocation 
     12   !!            3.5  ! 2012-10 (A. Coward, G. Madec) salt fluxes ; ice+snow mass 
    1213   !!---------------------------------------------------------------------- 
    1314#if defined key_lim3 
     
    4445   PUBLIC   lim_sbc_tau    ! called by sbc_ice_lim 
    4546 
    46    REAL(wp)  ::   r1_rdtice            ! = 1. / rdt_ice  
    4747   REAL(wp)  ::   epsi16 = 1.e-16_wp   ! constant values 
    4848   REAL(wp)  ::   rzero  = 0._wp     
     
    8888      !!              - qns     : sea heat flux: non solar 
    8989      !!              - emp     : freshwater budget: volume flux  
    90       !!              - sfx     : freshwater budget: concentration/dillution  
     90      !!              - sfx     : salt flux  
    9191      !!              - fr_i    : ice fraction 
    9292      !!              - tn_ice  : sea-ice surface temperature 
     
    102102      INTEGER  ::   ifvt, i1mfr, idfr               ! some switches 
    103103      INTEGER  ::   iflt, ial, iadv, ifral, ifrdv 
    104       REAL(wp) ::   zinda, zfons, zpme              ! local scalars 
    105       REAL(wp), POINTER, DIMENSION(:,:) ::   zfcm1 , zfcm2    ! solar/non solar heat fluxes 
    106       REAL(wp), POINTER, DIMENSION(:,:,:) ::   zalb, zalbp   ! 2D/3D workspace 
     104      REAL(wp) ::   zinda, zemp, zemp_snow, zfmm    ! local scalars 
     105      REAL(wp), POINTER, DIMENSION(:,:)   ::   zfcm1 , zfcm2   ! solar/non solar heat fluxes 
     106      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zalb, zalbp     ! 2D/3D workspace 
    107107      !!--------------------------------------------------------------------- 
    108108       
     
    153153               !              &           + iflt * ffltbif(ji,jj) !!! only if one category is used 
    154154               &           + ifral   * ( ial * qcmif(ji,jj) + (1 - ial) * qldif(ji,jj) ) * r1_rdtice   & 
    155                &           + ifrdv   * ( qfvbq(ji,jj) + qdtcn(ji,jj) )                  * r1_rdtice   & 
    156                &           + fhmec(ji,jj)     & ! new contribution due to snow melt in ridging!! 
     155               &           + ifrdv   * (       qfvbq(ji,jj) +             qdtcn(ji,jj) ) * r1_rdtice   & 
     156               &           + fhmec(ji,jj)     & ! new contribution due to snow melt when ridging!! 
    157157               &           + fheat_rpo(ji,jj) & ! contribution from ridge formation 
    158158               &           + fheat_res(ji,jj) 
    159             ! fscmbq  Part of the solar radiation transmitted through the ice and going to the ocean 
    160             !         computed in limthd_zdf.F90 
     159            ! fscmbq  Part of the solar radiation transmitted through the ice and going to the ocean computed in limthd_zdf.F90 
    161160            ! ffltbif Total heat content of the ice (brine pockets+ice) / delta_t 
    162161            ! qcmif   Energy needed to bring the ocean surface layer until its freezing (ok) 
     
    167166            ! qdtcn Energy from the turbulent oceanic heat flux heat flux coming in the lead 
    168167 
    169             IF ( num_sal == 2 ) zfcm2(ji,jj) = zfcm2(ji,jj) + & 
    170                fhbri(ji,jj) ! new contribution due to brine drainage  
    171  
    172             ! bottom radiative component is sent to the computation of the 
    173             ! oceanic heat flux 
     168            IF( num_sal == 2 )   zfcm2(ji,jj) = zfcm2(ji,jj) + fhbri(ji,jj)    ! add contribution due to brine drainage  
     169 
     170            ! bottom radiative component is sent to the computation of the oceanic heat flux 
    174171            fsbbq(ji,jj) = ( 1.0 - ( ifvt + iflt ) ) * fscmbq(ji,jj)      
    175172 
     
    179176            !                           ! fdtcn : turbulent oceanic heat flux 
    180177 
    181             !!gm   this IF prevents the vertorisation of the whole loop 
     178!!gm   this IF prevents the vertorisation of the whole loop 
    182179            IF ( ( ji == jiindx ) .AND. ( jj == jjindx) ) THEN 
    183180               WRITE(numout,*) ' lim_sbc : heat fluxes ' 
     
    208205               WRITE(numout,*) ' fheat_res : ', fheat_res(jiindx,jjindx) 
    209206            ENDIF 
    210             !!gm   end 
     207!!gm   end 
    211208         END DO 
    212209      END DO 
     
    229226 
    230227            !  computing freshwater exchanges at the ice/ocean interface 
    231             zpme = - emp(ji,jj)     * ( 1.0 - at_i(ji,jj)          )  &   ! evaporation over oceanic fraction 
    232                &   + tprecip(ji,jj) *         at_i(ji,jj)             &   ! all precipitation reach the ocean 
    233                &   - sprecip(ji,jj) * ( 1. - (pfrld(ji,jj)**betas) )  &   ! except solid precip intercepted by sea-ice 
    234                &   - rdm_snw(ji,jj) * r1_rdtice                       &   ! freshwaterflux due to snow melting  
    235                &   + fmmec(ji,jj)                                         ! snow falling when ridging 
    236  
    237  
    238             !  computing salt exchanges at the ice/ocean interface 
    239             !  sice should be the same as computed with the ice model 
    240             zfons =  ( soce_0(ji,jj) - sice_0(ji,jj) ) * rdm_ice(ji,jj) * r1_rdtice  
    241             ! SOCE 
    242             zfons =  ( sss_m (ji,jj) - sice_0(ji,jj) ) * rdm_ice(ji,jj) * r1_rdtice 
    243  
    244             !CT useless            !  salt flux for constant salinity 
    245             !CT useless            fsalt(ji,jj)      =  zfons / ( sss_m(ji,jj) + epsi16 ) + fsalt_res(ji,jj) 
    246             !  salt flux for variable salinity 
    247             zinda             = 1.0 - MAX( rzero , SIGN( rone , - ( 1.0 - pfrld(ji,jj) ) ) ) 
    248             !  correcting brine and salt fluxes 
    249             fsbri(ji,jj)      =  zinda*fsbri(ji,jj) 
    250             !  converting the salt fluxes from ice to a freshwater flux from ocean 
    251             fsalt_res(ji,jj)  =  fsalt_res(ji,jj) / ( sss_m(ji,jj) + epsi16 ) 
    252             fseqv(ji,jj)      =  fseqv(ji,jj)     / ( sss_m(ji,jj) + epsi16 ) 
    253             fsbri(ji,jj)      =  fsbri(ji,jj)     / ( sss_m(ji,jj) + epsi16 ) 
    254             fsalt_rpo(ji,jj)  =  fsalt_rpo(ji,jj) / ( sss_m(ji,jj) + epsi16 ) 
    255  
    256             !  freshwater mass exchange (positive to the ice, negative for the ocean ?) 
    257             !  actually it's a salt flux (so it's minus freshwater flux) 
    258             !  if sea ice grows, zfons is positive, fsalt also 
    259             !  POSITIVE SALT FLUX FROM THE ICE TO THE OCEAN 
    260             !  POSITIVE FRESHWATER FLUX FROM THE OCEAN TO THE ICE [kg.m-2.s-1] 
    261  
    262             emp(ji,jj) = - zpme  
     228            zemp =   emp(ji,jj)     * ( 1.0 - at_i(ji,jj)          )  &   ! evaporation over oceanic fraction 
     229               &   - tprecip(ji,jj) *         at_i(ji,jj)             &   ! all precipitation reach the ocean 
     230               &   + sprecip(ji,jj) * ( 1. - (pfrld(ji,jj)**betas) )  &   ! except solid precip intercepted by sea-ice 
     231               &   - fmmec(ji,jj)                                         ! snow falling when ridging 
     232 
     233            ! mass flux at the ocean/ice interface (sea ice fraction) 
     234            zemp_snw = rdm_snw(ji,jj) * r1_rdtice                         ! snow melting = pure water that enters the ocean 
     235            zfmm     = rdm_ice(ji,jj) * r1_rdtice                         ! Freezing minus mesting   
     236 
     237            emp(ji,jj) = zemp + zemp_snw + zfmm  ! mass flux + F/M mass flux (always ice/ocean mass exchange) 
     238             
     239            !  correcting brine salt fluxes   (zinda = 1  if pfrld=1 , =0 otherwise) 
     240            zinda        = 1.0 - MAX( rzero , SIGN( rone , - ( 1.0 - pfrld(ji,jj) ) ) ) 
     241            fsbri(ji,jj) = zinda * fsbri(ji,jj) 
    263242         END DO 
    264243      END DO 
    265244 
     245      !------------------------------------------! 
     246      !      salt flux at the ocean surface      ! 
     247      !------------------------------------------! 
     248 
    266249      IF( num_sal == 2 ) THEN      ! variable ice salinity: brine drainage included in the salt flux 
    267          sfx (:,:) = fsbri(:,:) + fseqv(:,:) + fsalt_res(:,:) + fsalt_rpo(:,:) + emp(:,:) 
     250         sfx (:,:) = fseqv(:,:) + fsalt_res(:,:) + fsalt_rpo(:,:) + fsbri(:,:) 
    268251      ELSE                         ! constant ice salinity: 
    269          sfx (:,:) =              fseqv(:,:) + fsalt_res(:,:) + fsalt_rpo(:,:) + emp(:,:) 
     252         sfx (:,:) = fseqv(:,:) + fsalt_res(:,:) + fsalt_rpo(:,:) 
    270253      ENDIF 
    271254      !-----------------------------------------------! 
     
    277260         snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
    278261         !                                                      ! time evolution of snow+ice mass 
    279          snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) / rdt_ice 
     262         snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) * r1_rdtice 
    280263      ENDIF 
    281264 
     
    403386      !                                      ! allocate lim_sbc array 
    404387      IF( lim_sbc_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'lim_sbc_init : unable to allocate standard arrays' ) 
    405       ! 
    406       r1_rdtice = 1. / rdt_ice 
    407388      ! 
    408389      soce_0(:,:) = soce                     ! constant SSS and ice salinity used in levitating sea-ice case 
Note: See TracChangeset for help on using the changeset viewer.