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 3962 for branches/2013/dev_r3406_CNRS_LIM3 – NEMO

Ignore:
Timestamp:
2013-07-09T14:22:30+02:00 (11 years ago)
Author:
gm
Message:

dev_r3406_CNRS_LIM3: fix a bug in the freshwater budget correction, see ticket #1116

Location:
branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r3938 r3962  
    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 
    1212   !!             -   ! 2012    (D. Iovino) salt flux change 
    1313   !!             -   ! 2012-05 (C. Rousset) add penetration solar flux 
     14   !!            3.5  ! 2012-10 (A. Coward, G. Madec) salt fluxes ; ice+snow mass 
    1415   !!---------------------------------------------------------------------- 
    1516#if defined key_lim3 
     
    3738   USE cpl_oasis3, ONLY : lk_cpl 
    3839   USE traqsr           ! clem: add penetration of solar flux into the calculation of heat budget 
    39    USE lib_fortran      ! to use key_nosignedzero 
     40   USE oce,        ONLY : sshn, sshb, snwice_mass, snwice_mass_b, snwice_fmass, sshu_b, sshv_b, sshu_n, sshv_n, sshf_n 
     41   USE dom_ice,    ONLY : tms 
     42   USE lib_fortran      ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    4043 
    4144   IMPLICIT NONE 
     
    173176            ! qdtcn Energy from the turbulent oceanic heat flux heat flux coming in the lead 
    174177 
    175             IF ( num_sal == 2 ) zfcm2(ji,jj) = zfcm2(ji,jj) + & 
    176                fhbri(ji,jj) ! new contribution due to brine drainage  
     178            IF ( num_sal == 2 ) zfcm2(ji,jj) = zfcm2(ji,jj) + fhbri(ji,jj) ! new contribution due to brine drainage  
    177179 
    178180            ! bottom radiative component is sent to the computation of the 
     
    281283      ENDIF 
    282284 
     285      !-----------------------------------------------! 
     286      !   mass of snow and ice per unit area          ! 
     287      !-----------------------------------------------! 
     288      IF( nn_ice_embd /= 0 ) THEN                               ! embedded sea-ice (mass required) 
     289         snwice_mass_b(:,:) = snwice_mass(:,:)                  ! save mass from the previous ice time step 
     290         !                                                      ! new mass per unit area 
     291         snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )  
     292         !                                                      ! time evolution of snow+ice mass 
     293         snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) * r1_rdtice 
     294      ENDIF 
    283295 
    284296      !-----------------------------------------------! 
     
    420432      oatte(:,:) = 1._wp 
    421433      ! 
     434      !                                      ! sea ice  with mass exchange 
     435         snwice_mass  (:,:) = tms(:,:) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  ) 
     436         snwice_mass_b(:,:) = snwice_mass(:,:) 
     437      ! 
     438      ! 
    422439   END SUBROUTINE lim_sbc_init 
    423440 
  • branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/SBC/sbcfwb.F90

    r3952 r3962  
    5959      !!                =3 global mean of emp set to zero at each nn_fsbc time step 
    6060      !!                   & spread out over erp area depending its sign 
     61      !! Note: if mass exchanges between ice and ocean, it is taken into account  
     62      !!       when computing the budget  
    6163      !!---------------------------------------------------------------------- 
    6264      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index 
     
    8789         ! 
    8890         area = glob_sum( e1e2t(:,:) )           ! interior global domain surface 
     91         ! 
     92!!#if ! defined key_lim2 &&  ! defined key_lim3 && ! defined key_cice  
     93#if ! defined key_lim3  
     94         snwice_mass_b(:,:) = 0._wp              ! no sea-ice model is being used : no snow+ice mass 
     95         snwice_mass  (:,:) = 0._wp 
     96         snwice_fmass (:,:) = 0._wp  
     97#endif 
     98         ! 
    8999      ENDIF 
    90100       
     
    95105         ! 
    96106         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN 
    97             z_fwf = glob_sum( e1e2t(:,:) * ( emp(:,:) - rnf(:,:) ) ) / area   ! sum over the global domain 
     107            z_fwf = glob_sum( e1e2t(:,:) * ( emp(:,:) - rnf(:,:) - snwice_fmass(:,:) ) ) / area   ! sum over the global domain 
    98108            emp (:,:) = emp (:,:) - z_fwf  
    99109            erp (:,:) = erp (:,:) - z_fwf  
     
    120130         ikty = 365 * 86400 / rdttra(1)    !!bug  use of 365 days leap year or 360d year !!!!!!! 
    121131         IF( MOD( kt, ikty ) == 0 ) THEN 
    122             a_fwb_b = a_fwb 
    123             a_fwb   = glob_sum( e1e2t(:,:) * sshn(:,:) )   ! sum over the global domain 
     132            a_fwb_b = a_fwb                           ! mean sea level taking into account the ice+snow 
     133                                                      ! sum over the global domain 
     134            a_fwb   = glob_sum( e1e2t(:,:) * ( sshn(:,:) + snwice_mass(:,:) * r1_rau0 ) ) 
    124135            a_fwb   = a_fwb * 1.e+3 / ( area * 86400. * 365. )     ! convert in Kg/m3/s = mm/s 
    125136!!gm        !                                                      !!bug 365d year  
     
    151162            zsurf_neg = glob_sum( e1e2t(:,:)*ztmsk_neg(:,:) )   ! Area filled by <0 and >0 erp  
    152163            zsurf_pos = glob_sum( e1e2t(:,:)*ztmsk_pos(:,:) ) 
    153             !                                                  ! fwf global mean  
    154             z_fwf = glob_sum( e1e2t(:,:) * ( emp(:,:) - rnf(:,:) ) ) / area 
     164            !                                                  ! fwf global mean (excluding ocean to ice/snow exchanges)  
     165            z_fwf     = glob_sum( e1e2t(:,:) * ( emp(:,:) - rnf(:,:) - snwice_fmass(:,:) ) ) / area 
    155166            !             
    156167            IF( z_fwf < 0._wp ) THEN         ! spread out over >0 erp area to increase evaporation 
     
    166177            z_fwf_nsrf =  zsum_fwf / ( zsurf_tospread + rsmall ) 
    167178            !                                                  ! weight to respect erp field 2D structure  
    168             zsum_erp = glob_sum( ztmsk_tospread(:,:) * erp(:,:) * e1e2t(:,:) ) 
     179            zsum_erp   = glob_sum( ztmsk_tospread(:,:) * erp(:,:) * e1e2t(:,:) ) 
    169180            z_wgt(:,:) = ztmsk_tospread(:,:) * erp(:,:) / ( zsum_erp + rsmall ) 
    170181            !                                                  ! final correction term to apply 
  • branches/2013/dev_r3406_CNRS_LIM3/NEMOGCM/NEMO/OPA_SRC/oce.F90

    r3294 r3962  
    4747   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gru , grv    !: horizontal gradient of rd at bottom u-point 
    4848 
     49   !! arrays relating to embedding ice in the ocean. These arrays need to be declared  
     50   !! even if no ice model is required. In the no ice model or traditional levitating  
     51   !! ice cases they contain only zeros 
     52   !! --------------------- 
     53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass        !: mass of snow and ice at current  ice time step   [Kg/m2] 
     54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_mass_b      !: mass of snow and ice at previous ice time step   [Kg/m2] 
     55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   snwice_fmass       !: time evolution of mass of snow+ice               [Kg/m2/s] 
     56 
    4957   !!---------------------------------------------------------------------- 
    5058   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
Note: See TracChangeset for help on using the changeset viewer.