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 11656 – NEMO

Changeset 11656


Ignore:
Timestamp:
2019-10-04T21:03:26+02:00 (5 years ago)
Author:
mathiot
Message:

ENHANCE-03_closea: add heat/fw fluxes output from closed seas + rm useless USE statements + add USE ONLY when reasonable + ensure heat conservation during the redistribution process (ticket #2143)

Location:
NEMO/branches/2019/ENHANCE-03_closea
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/ENHANCE-03_closea/cfgs/SHARED/field_def_nemo-oce.xml

    r10824 r11656  
    250250          <field id="runoffs"      long_name="River Runoffs"                        standard_name="water_flux_into_sea_water_from_rivers"                                unit="kg/m2/s"   /> 
    251251          <field id="precip"       long_name="Total precipitation"                  standard_name="precipitation_flux"                                                   unit="kg/m2/s"   /> 
     252          <field id="wclosea"      long_name="closed sea empmr correction"          standard_name="closea_empmr"                                                         unit="kg/m2/s"   /> 
    252253      
    253254          <field id="qt"           long_name="Net Downward Heat Flux"                standard_name="surface_downward_heat_flux_in_sea_water"                              unit="W/m2"                           /> 
     
    256257          <field id="qsr3d"        long_name="Shortwave Radiation 3D distribution"   standard_name="downwelling_shortwave_flux_in_sea_water"                              unit="W/m2"      grid_ref="grid_T_3D" /> 
    257258          <field id="qrp"          long_name="Surface Heat Flux: Damping"            standard_name="heat_flux_into_sea_water_due_to_newtonian_relaxation"                 unit="W/m2"                           /> 
     259          <field id="qclosea"      long_name="closed sea heat content flux"          standard_name="closea_heat_content_downward_flux"                                    unit="W/m2"     /> 
    258260          <field id="erp"          long_name="Surface Water Flux: Damping"           standard_name="water_flux_out_of_sea_water_due_to_newtonian_relaxation"              unit="kg/m2/s"                        /> 
    259261          <field id="taum"         long_name="wind stress module"                    standard_name="magnitude_of_surface_downward_stress"                                 unit="N/m2"                           /> 
  • NEMO/branches/2019/ENHANCE-03_closea/cfgs/SHARED/namelist_ref

    r11207 r11656  
    9696&namclo        !   parameters of the closed sea (cs) behavior                (default: OFF) 
    9797!----------------------------------------------------------------------- 
    98    ln_maskcs = .false.           ! (=T) cs are masked ;  
    99       !                          ! (=F) cs masks are read and net evap/precip over closed sea spread out depending on domain_cfg.nc masks 
    100       !                          ! see ln_mask_csundef and ln_clo_rnf for specific option related to this case 
     98   ln_maskcs = .false.        ! (=T) cs are masked ; So, in this case ln_mask_csundef and ln_clo_rnf have no effect. 
     99      !                       ! (=F => set ln_mask_csundef and ln_clo_rnf)  
     100      !                       ! cs masks are read and net evap/precip over closed sea spread out depending on domain_cfg.nc masks. 
     101      !                       ! See ln_mask_csundef and ln_clo_rnf for specific option related to this case 
    101102      ! 
    102       ln_mask_csundef = .false.  ! (=T) undefined closed seas are masked ;  
     103      ln_mask_csundef = .true.   ! (=T) undefined closed seas are masked ;  
    103104      !                          ! (=F) undefined closed seas are kept and no specific treatment is done for these closed seas 
    104105      ! 
    105       ln_clo_rnf = .false.       ! (=T) river mouth specified in domain_cfg.nc masks (rnf and emp case) are added to the runoff mask. 
     106      ln_clo_rnf = .true.        ! (=T) river mouth specified in domain_cfg.nc masks (rnf and emp case) are added to the runoff mask. 
    106107      !                          !      allow the treatment of closed sea outflow grid-points to be the same as river mouth grid-points 
    107108/ 
  • NEMO/branches/2019/ENHANCE-03_closea/src/OCE/DOM/closea.F90

    r11629 r11656  
    1919   !!   clo_msk    : set to zero a field over closed sea (see domzgr) 
    2020   !!---------------------------------------------------------------------- 
    21    USE oce             ! dynamics and tracers 
    22    USE dom_oce         ! ocean space and time domain 
    23    USE phycst          ! physical constants 
    24    USE sbc_oce         ! ocean surface boundary conditions 
    25    USE iom             ! I/O routines 
     21   USE in_out_manager  ! I/O manager 
    2622   ! 
    27    USE in_out_manager  ! I/O manager 
    28    USE lib_fortran,    ONLY: glob_sum 
    29    USE lbclnk          ! lateral boundary condition - MPP exchanges 
    30    USE lib_mpp         ! MPP library 
    31    USE timing          ! Timing 
     23   USE diurnal_bulk, ONLY: ln_diurnal_only            ! used for sanity check 
     24   USE iom         , ONLY: iom_open, iom_get, iom_close, jpdom_data ! I/O routines 
     25   USE lib_fortran , ONLY: glob_sum                   ! fortran library 
     26   USE lib_mpp     , ONLY: mpp_max, ctl_nam, ctl_stop ! MPP library 
    3227 
    3328   IMPLICIT NONE 
    34    PRIVATE read_csmask 
    35    PRIVATE alloc_csmask 
     29 
     30   PRIVATE 
    3631 
    3732   PUBLIC dom_clo      ! called by domain module 
     
    5045   INTEGER, PUBLIC :: ncse      !: number of closed seas empmr  mappings (inferred from closea_mask_emp field) 
    5146 
    52    INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_opnsea, mask_csundef !: mask defining the open sea and the undefined closed sea 
     47   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_opnsea, mask_csundef  !: mask defining the open sea and the undefined closed sea 
    5348  
    54    INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csglo, mask_csgrpglo !: mask of integers defining closed seas 
    55    INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csrnf, mask_csgrprnf !: mask of integers defining closed seas rnf mappings 
    56    INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csemp, mask_csgrpemp !: mask of integers defining closed seas empmr mappings 
     49   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csglo , mask_csgrpglo !: mask of integers defining closed seas 
     50   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csrnf , mask_csgrprnf !: mask of integers defining closed seas rnf mappings 
     51   INTEGER, PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:) :: mask_csemp , mask_csgrpemp !: mask of integers defining closed seas empmr mappings 
    5752 
    5853   !! * Substitutions 
     
    9792      IF(lwp) WRITE(numout,*)'dom_clo : read in masks to define closed seas ' 
    9893      IF(lwp) WRITE(numout,*)'~~~~~~~' 
     94      IF(lwp) WRITE(numout,*) 
    9995      !! 
    10096      !! check option compatibility 
     
    116112      IF ( ln_maskcs ) THEN 
    117113         ! closed sea are masked 
     114         IF(lwp) WRITE(numout,*)'          ln_maskcs = T : all closed seas are masked' 
     115         IF(lwp) WRITE(numout,*) 
    118116         ! no special treatment of closed sea 
    119117         ! no redistribution of emp unbalance over closed sea into river mouth/open ocean 
     
    121119      ELSE 
    122120         ! redistribution of emp unbalance over closed sea into river mouth/open ocean 
     121         IF(lwp) WRITE(numout,*)'          ln_maskcs = F : net emp is corrected over defined closed seas' 
     122         ! 
    123123         l_sbc_clo = .true. 
    124124         ! 
     
    126126         IF ( ln_clo_rnf) l_clo_rnf = .true. 
    127127         ! 
    128          ! closed sea not defined (ie not in the domcfg namelist used to build the domcfg.nc file) are masked  
    129128         IF ( ln_mask_csundef) THEN 
     129            ! closed sea not defined (ie not in the domcfg namelist used to build the domcfg.nc file) are masked  
     130            IF(lwp) WRITE(numout,*)'          ln_mask_csundef = T : all undefined closed seas are masked' 
     131            ! 
    130132            CALL alloc_csmask( mask_csundef ) 
    131133            CALL read_csmask( cn_domcfg, 'mask_csundef', mask_csundef ) 
    132134            ! revert the mask for masking of undefined closed seas in domzgr  
    133135            ! (0 over the undefined closed sea and 1 elsewhere) 
    134             mask_csundef = 1 - mask_csundef 
     136            mask_csundef(:,:) = 1 - mask_csundef(:,:) 
    135137         END IF 
     138         IF(lwp) WRITE(numout,*) 
    136139         ! 
    137140         ! allocate source mask for each cases 
  • NEMO/branches/2019/ENHANCE-03_closea/src/OCE/DOM/domain.F90

    r11207 r11656  
    3030   USE trc_oce        ! shared ocean & passive tracers variab 
    3131   USE phycst         ! physical constants 
    32    USE closea         ! closed seas 
    3332   USE domhgr         ! domain: set the horizontal mesh 
    3433   USE domzgr         ! domain: set the vertical mesh 
     
    3837   USE c1d            ! 1D configuration 
    3938   USE dyncor_c1d     ! 1D configuration: Coriolis term    (cor_c1d routine) 
    40    USE wet_dry,  ONLY : ll_wd 
     39   USE wet_dry, ONLY : ll_wd 
     40   USE closea , ONLY : dom_clo ! closed seas 
    4141   ! 
    4242   USE in_out_manager ! I/O manager 
  • NEMO/branches/2019/ENHANCE-03_closea/src/OCE/SBC/sbcclo.F90

    r11629 r11656  
    2222   !!---------------------------------------------------------------------- 
    2323   ! 
    24    USE oce             ! dynamics and tracers 
    25    USE dom_oce         ! ocean space and time domain 
    26    USE closea          ! closed sea  
    27    USE phycst          ! physical constants 
    28    USE sbc_oce         ! ocean surface boundary conditions 
    29    USE iom             ! I/O routines 
    30    ! 
    31    USE in_out_manager  ! I/O manager 
    32    USE lib_fortran,    ONLY: glob_sum 
    33    USE lib_mpp         ! MPP library 
     24   USE closea                                  ! closed sea  
     25   USE in_out_manager                          ! I/O manager 
     26   ! 
     27   USE dom_oce,     ONLY: e1e2t                ! ocean space and time domain 
     28   USE phycst ,     ONLY: rcp                  ! physical constants 
     29   USE sbc_oce,     ONLY: emp, qns, rnf, sst_m ! ocean surface boundary conditions 
     30   USE iom    ,     ONLY: iom_put              ! I/O routines 
     31   USE lib_fortran, ONLY: glob_sum             ! fortran library 
     32   USE lib_mpp    , ONLY: mpp_min, ctl_stop    ! MPP library 
    3433   ! 
    3534   IMPLICIT NONE 
     
    270269      INTEGER, DIMENSION(jpi,jpj) :: imsk_src, imsk_trg  ! tmp array source and target closed sea masks 
    271270       
    272       REAL(wp) :: zcoef, zcoef1, ztmp ! tmp 
    273       REAL(wp) :: zcsfwf              ! tmp net fwf over one closed sea 
    274       REAL(wp) :: zsurftrg            ! tmp target surface area 
     271      REAL(wp) :: zcsfw, zcsh        ! total fresh water and associated heat over one closed sea 
     272      REAL(wp) :: zcsfwf             ! mean fresh water flux over one closed sea 
     273      REAL(wp) :: zsurftrg, zsurfsrc ! total target surface area 
    275274      !!---------------------------------------------------------------------- 
    276275      ! 
    277276      DO jcs = 1, kncs  ! loop over closed seas 
    278277         ! 
    279          !! 0. get mask of the closed sea 
    280          imsk_src(:,:) = 0 
    281          WHERE ( kmsk_src(:,:) == jcs ) imsk_src(:,:) = 1 
    282          ! 
    283          !! 1. Work out net freshwater fluxes over the closed sea from EMP - RNF. 
     278         !! 0. get mask and surface of the closed sea 
     279         ! mask src 
     280         WHERE ( kmsk_src(:,:) == jcs )  
     281            imsk_src(:,:) = 1 
     282         ELSEWHERE 
     283            imsk_src(:,:) = 0 
     284         END WHERE 
     285         ! area src 
     286         zsurfsrc = psurfsrc(jcs) 
     287         ! 
     288         !! 1. Work out net freshwater over the closed sea from EMP - RNF. 
     289         !!    Work out net heat associated with the correction (needed for conservation) 
    284290         !!    (PM: should we consider used delayed glob sum ?) 
    285          zcsfwf = glob_sum( 'closea', e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * imsk_src(:,:) ) 
     291         zcsfw  = glob_sum( 'closea', e1e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * imsk_src(:,:) ) 
    286292         ! 
    287293         !! 2. Deal with runoff special case (net evaporation spread globally) 
    288294         !!    and compute trg mask 
    289          IF (cdcstype == 'rnf' .AND. zcsfwf > 0) THEN 
     295         IF (cdcstype == 'rnf' .AND. zcsfw  > 0._wp) THEN 
    290296            zsurftrg = psurf_opnsea(1)           ! change the target area surface 
    291297            imsk_trg = kcsgrp(jcs) * kmsk_opnsea ! trg mask is now the open sea mask 
     
    295301         END IF 
    296302         ! 
    297          !! 3. Add residuals to target points 
    298          zcoef  = zcsfwf / zsurftrg 
    299          zcoef1 = rcp * zcoef 
     303         !! 3. Subtract residuals from source points 
     304         zcsfwf = zcsfw / zsurfsrc 
     305         pwcs(:,:) = pwcs(:,:) -       zcsfwf              * imsk_src(:,:) 
     306         pqcs(:,:) = pqcs(:,:) + rcp * zcsfwf * sst_m(:,:) * imsk_src(:,:) 
     307         ! 
     308         !! 4. Add residuals to target points  
     309         !!    Do not use pqcs(:,:) = pqcs(:,:) - rcp * zcsfw  * sst_m(:,:) / zsurftrg  
     310         !!    as there is no reason for heat conservation with this formulation 
     311         zcsh   = glob_sum( 'closea', e1e2t(:,:) * rcp * zcsfwf * sst_m(:,:) * imsk_src(:,:) ) 
    300312         WHERE( imsk_trg(:,:) == kcsgrp(jcs) ) 
    301             pwcs(:,:) = pwcs(:,:) + zcoef 
    302             pqcs(:,:) = pqcs(:,:) - zcoef1 * sst_m(:,:) 
     313            pwcs(:,:) = pwcs(:,:) + zcsfw / zsurftrg 
     314            pqcs(:,:) = pqcs(:,:) - zcsh  / zsurftrg 
    303315         ENDWHERE 
    304          ! 
    305          !! 4. Subtract residuals from source points 
    306          zcoef    = zcsfwf / psurfsrc(jcs) 
    307          zcoef1   = rcp * zcoef 
    308          WHERE( kmsk_src(:,:) == jcs ) 
    309             pwcs(:,:) = pwcs(:,:) - zcoef 
    310             pqcs(:,:) = pqcs(:,:) + zcoef1 * sst_m(:,:) 
    311          ENDWHERE 
    312          ! WARNING (PM): the correction is done as it was done in the previous version 
    313          !               this do no conserve heat as there is no reason that  
    314          !               sum(zcoef1*sst_m) over the source (closed sea) (4) = sum(zcoef1*sst_m) over the target (river mouth) (3) 
    315316         ! 
    316317      END DO ! jcs 
  • NEMO/branches/2019/ENHANCE-03_closea/src/OCE/SBC/sbcrnf.F90

    r10523 r11656  
    2121   USE sbcisf         ! PM we could remove it I think 
    2222   USE eosbn2         ! Equation Of State 
    23    USE closea        ! closed seas 
     23   USE closea, ONLY: l_clo_rnf, clo_rnf ! closed seas 
    2424   ! 
    2525   USE in_out_manager ! I/O manager 
Note: See TracChangeset for help on using the changeset viewer.