Ignore:
Timestamp:
Feb 3, 2020, 2:27:46 PM (4 years ago)
Author:
lguez
Message:

If the ocean skin parameterization is working (passively or actively,
activate_ocean_skin >= 1) and we are coupled to the ocean then
receive bulk salinity of the surface layer of the ocean from the ocean
and feed it to procedure bulk_flux instead of the constant
value 35. If the ocean skin parameterization is working actively
(activate_ocean_skin == 2) and we are coupled to the ocean then send
ocean-air interface temperature to the ocean. We can only send
interface temperature from the previous time-step since communication
with the ocean is before the call to bulk_flux. In module cpl_mod,
define cpl_t_int with rank 1: no dimension for cpl_index because
t_int is only defined over ocean. New dummy argument sss of
procedures cpl_receive_ocean_fields and ocean_cpl_noice. New dummy
argument t_int of cpl_send_ocean_fields. In procedure
surf_ocean, rename local variable s1 to sss and give it the size
klon, which is required by the coupling machinery.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin/libf/phylmd/cpl_mod.F90

    r3605 r3627  
    4848  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_snow, cpl_evap, cpl_tsol
    4949  !$OMP THREADPRIVATE(cpl_snow,cpl_evap,cpl_tsol)
     50
     51  REAL, ALLOCATABLE, SAVE:: cpl_t_int(:)
     52  !$OMP THREADPRIVATE(cpl_t_int)
     53 
    5054  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_fder, cpl_albe, cpl_taux, cpl_tauy
    5155  !$OMP THREADPRIVATE(cpl_fder,cpl_albe,cpl_taux,cpl_tauy)
     
    6670  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_sit     ! sea ice temperature
    6771  !$OMP THREADPRIVATE(read_sit)
     72
     73  REAL, ALLOCATABLE, SAVE:: read_sss(:, :)
     74  ! bulk salinity of the surface layer of the ocean, in ppt
     75  !$OMP THREADPRIVATE(read_sss)
     76
    6877  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_sic     ! sea ice fraction
    6978  !$OMP THREADPRIVATE(read_sic)
     
    8493  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_snow2D, cpl_evap2D, cpl_tsol2D
    8594  !$OMP THREADPRIVATE(cpl_snow2D, cpl_evap2D, cpl_tsol2D)
     95
     96  REAL, ALLOCATABLE, SAVE:: cpl_t_int_2D(:,:)
     97  !$OMP THREADPRIVATE(cpl_t_int_2D)
     98
    8699  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_fder2D, cpl_albe2D
    87100  !$OMP THREADPRIVATE(cpl_fder2D, cpl_albe2D)
     
    122135    USE geometry_mod, ONLY : longitude_deg, latitude_deg, ind_cell_glo, cell_area
    123136    USE ioipsl_getin_p_mod, ONLY: getin_p
     137    use config_ocean_skin_m, only: activate_ocean_skin
    124138
    125139! Input arguments
     
    217231    ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error)
    218232    sum_error = sum_error + error
     233
     234    if (activate_ocean_skin >= 1) then
     235       ALLOCATE(read_sss(nbp_lon, jj_nb), stat = error)
     236       sum_error = sum_error + error
     237   
     238       if (activate_ocean_skin == 2) then
     239          ALLOCATE(cpl_t_int(klon), stat = error)
     240          sum_error = sum_error + error
     241       end if
     242    end if
     243
    219244    ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error)
    220245    sum_error = sum_error + error
     
    376401    USE time_phylmdz_mod, ONLY: start_time, itau_phy
    377402    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     403    use config_ocean_skin_m, only: activate_ocean_skin
    378404
    379405    INCLUDE "YOMCST.h"
     
    437463       read_alb_sic(:,:) = tab_read_flds(:,:,idr_icealw)  ! Albedo at sea ice
    438464       read_sit(:,:)     = tab_read_flds(:,:,idr_icetem)  ! Sea ice temperature
     465       if (activate_ocean_skin >= 1) read_sss(:,:) = tab_read_flds(:,:,idr_sss)
    439466!$OMP END MASTER
    440467
     
    494521!
    495522
    496   SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new, u0_new, v0_new)
     523  SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new, u0_new, &
     524       v0_new, sss)
    497525!
    498526! This routine returns the field for the ocean that has been read from the coupler
     
    502530    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
    503531    USE indice_sol_mod
     532    use config_ocean_skin_m, only: activate_ocean_skin
    504533
    505534! Input arguments
     
    511540!*************************************************************************************
    512541    REAL, DIMENSION(klon), INTENT(OUT)      :: tsurf_new
     542
     543    REAL, INTENT(OUT):: sss(:) ! (klon)
     544    ! bulk salinity of the surface layer of the ocean, in ppt
     545
    513546    REAL, DIMENSION(klon), INTENT(OUT)      :: u0_new
    514547    REAL, DIMENSION(klon), INTENT(OUT)      :: v0_new
     
    525558!*************************************************************************************
    526559    CALL cpl2gath(read_sst, tsurf_new, knon, knindex)
     560    if (activate_ocean_skin >= 1) CALL cpl2gath(read_sss, sss, knon, knindex)
    527561    CALL cpl2gath(read_sic, sic_new, knon, knindex)
    528562    CALL cpl2gath(read_u0, u0_new, knon, knindex)
     
    611645       swdown, lwdown, fluxlat, fluxsens, &
    612646       precip_rain, precip_snow, evap, tsurf, fder, albsol, taux, tauy, windsp,&
    613        sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
    614 !
    615 ! This subroutine cumulates some fields for each time-step during a coupling
    616 ! period. At last time-step in a coupling period the fields are transformed to the
    617 ! grid accepted by the coupler. No sending to the coupler will be done from here
    618 ! (it is done in cpl_send_seaice_fields).
    619 !
     647       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, t_int)
     648
     649    ! This subroutine cumulates some fields for each time-step during
     650    ! a coupling period. At last time-step in a coupling period the
     651    ! fields are transformed to the grid accepted by the coupler. No
     652    ! sending to the coupler will be done from here (it is done in
     653    ! cpl_send_seaice_fields). Crucial hypothesis is that the surface
     654    ! fractions do not change between coupling time-steps.
     655
    620656    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    621657    USE indice_sol_mod
    622658    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     659    use config_ocean_skin_m, only: activate_ocean_skin
    623660
    624661! Input arguments
     
    634671    REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
    635672    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
     673    real, intent(in):: t_int(:) ! (klon) ocean-air interface temperature, in K
    636674
    637675! Local variables
     
    669707       cpl_taumod(1:knon,cpl_index) = 0.0
    670708       IF (carbon_cycle_cpl) cpl_atm_co2(1:knon,cpl_index) = 0.0
     709       if (activate_ocean_skin == 2) cpl_t_int(:knon) = 0.
    671710    ENDIF
    672711       
     
    710749!!---OB: this is correct but why knindex ??
    711750       ENDIF
     751
     752       if (activate_ocean_skin == 2) &
     753            cpl_t_int(ig) = cpl_t_int(ig) + t_int(ig) / REAL(nexca)
    712754     ENDDO
    713755
     
    755797             sum_error = sum_error + error
    756798          ENDIF
     799
     800          if (activate_ocean_skin == 2) then
     801             ALLOCATE(cpl_t_int_2D(nbp_lon, jj_nb), stat = error)
     802             sum_error = sum_error + error
     803          end if
    757804
    758805          IF (sum_error /= 0) THEN
     
    810857       IF (carbon_cycle_cpl) &
    811858            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
    812    ENDIF
     859       if (activate_ocean_skin == 2) &
     860            CALL gath2cpl(cpl_t_int, cpl_t_int_2D, knon, knindex)
     861    ENDIF
    813862
    814863  END SUBROUTINE cpl_send_ocean_fields
     
    11451194    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    11461195    USE time_phylmdz_mod, ONLY: start_time, itau_phy
     1196    use config_ocean_skin_m, only: activate_ocean_skin
    11471197! Some includes
    11481198!   
     
    12021252    tab_flds(:,:,ids_qraiic) = cpl_sens_rain2D(:,:,2)
    12031253    tab_flds(:,:,ids_qsnoic) = cpl_sens_snow2D(:,:,2)
     1254    if (activate_ocean_skin == 2) tab_flds(:, :, ids_t_int) = cpl_t_int_2D
    12041255   
    12051256    IF (version_ocean=='nemo') THEN
     
    14381489    ENDIF
    14391490
     1491    if (activate_ocean_skin == 2) deallocate(cpl_t_int_2d)
     1492
    14401493    IF (sum_error /= 0) THEN
    14411494       abort_message='Pb in deallocation of cpl_xxxx2D coupling variables'
Note: See TracChangeset for help on using the changeset viewer.