Ignore:
Timestamp:
Feb 22, 2021, 12:44:07 PM (4 years ago)
Author:
dcugnet
Message:

Update the branch to the current trunk.

Location:
LMDZ6/branches/LMDZ-tracers
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ-tracers

  • LMDZ6/branches/LMDZ-tracers/libf/phylmd/cpl_mod.F90

    r3494 r3851  
    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_delta_sst(:), cpl_delta_sal(:)
     52  !$OMP THREADPRIVATE(cpl_delta_sst, cpl_delta_sal)
     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_delta_sst_2D(:,:), cpl_delta_sal_2D(:,:)
     97  !$OMP THREADPRIVATE(cpl_delta_sst_2D, cpl_delta_sal_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
     
    153167    cpl_old_calving=.FALSE.
    154168    CALL getin_p("cpl_old_calving",cpl_old_calving)
     169    WRITE(lunout,*)' cpl_old_calving = ', cpl_old_calving
    155170
    156171
     
    217232    ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error)
    218233    sum_error = sum_error + error
     234
     235    if (activate_ocean_skin >= 1) then
     236       ALLOCATE(read_sss(nbp_lon, jj_nb), stat = error)
     237       sum_error = sum_error + error
     238   
     239       if (activate_ocean_skin == 2) then
     240          ALLOCATE(cpl_delta_sst(klon), cpl_delta_sal(klon), stat = error)
     241          sum_error = sum_error + error
     242       end if
     243    end if
     244
    219245    ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error)
    220246    sum_error = sum_error + error
     
    240266    ALLOCATE(cell_area2D(nbp_lon, jj_nb), stat = error)   
    241267    sum_error = sum_error + error
    242 
    243268
    244269    CALL gather_omp(longitude_deg,rlon_mpi)
     
    251276      CALL Grid1DTo2D_mpi(rlat_mpi,lat2D)
    252277      CALL Grid1DTo2D_mpi(cell_area_mpi,cell_area2D)
     278      !--the next line is required for lat-lon grid and should have no impact
     279      !--for an unstructured grid for which nbp_lon=1
     280      !--if north pole in process mpi then divide cell area of pole cell by number of replicates
     281      IF (is_north_pole_dyn) cell_area2D(:,1)=cell_area2D(:,1)/FLOAT(nbp_lon)
     282      !--if south pole in process mpi then divide cell area of pole cell by number of replicates
     283      IF (is_south_pole_dyn) cell_area2D(:,jj_nb)=cell_area2D(:,jj_nb)/FLOAT(nbp_lon)
    253284      mask_calving(:,:,:) = 0
    254285      WHERE ( lat2D >= 40) mask_calving(:,:,1) = 1
     
    278309    ENDIF
    279310   
    280            
    281311    IF (sum_error /= 0) THEN
    282312       abort_message='Pb allocation variables couplees'
     
    349379    ENDIF    ! is_sequential
    350380   
    351 
    352381!*************************************************************************************
    353382! compatibility test
     
    376405    USE time_phylmdz_mod, ONLY: start_time, itau_phy
    377406    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     407    use config_ocean_skin_m, only: activate_ocean_skin
    378408
    379409    INCLUDE "YOMCST.h"
     
    437467       read_alb_sic(:,:) = tab_read_flds(:,:,idr_icealw)  ! Albedo at sea ice
    438468       read_sit(:,:)     = tab_read_flds(:,:,idr_icetem)  ! Sea ice temperature
     469       if (activate_ocean_skin >= 1) read_sss(:,:) = tab_read_flds(:,:,idr_sss)
    439470!$OMP END MASTER
    440471
     
    494525!
    495526
    496   SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new, u0_new, v0_new)
     527  SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new, u0_new, &
     528       v0_new, sss)
    497529!
    498530! This routine returns the field for the ocean that has been read from the coupler
     
    502534    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
    503535    USE indice_sol_mod
     536    use config_ocean_skin_m, only: activate_ocean_skin
    504537
    505538! Input arguments
     
    511544!*************************************************************************************
    512545    REAL, DIMENSION(klon), INTENT(OUT)      :: tsurf_new
     546
     547    REAL, INTENT(OUT):: sss(:) ! (klon)
     548    ! bulk salinity of the surface layer of the ocean, in ppt
     549
    513550    REAL, DIMENSION(klon), INTENT(OUT)      :: u0_new
    514551    REAL, DIMENSION(klon), INTENT(OUT)      :: v0_new
     
    525562!*************************************************************************************
    526563    CALL cpl2gath(read_sst, tsurf_new, knon, knindex)
     564    if (activate_ocean_skin >= 1) CALL cpl2gath(read_sss, sss, knon, knindex)
    527565    CALL cpl2gath(read_sic, sic_new, knon, knindex)
    528566    CALL cpl2gath(read_u0, u0_new, knon, knindex)
     
    611649       swdown, lwdown, fluxlat, fluxsens, &
    612650       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 !
     651       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, delta_sst, &
     652       delta_sal)
     653
     654    ! This subroutine cumulates some fields for each time-step during
     655    ! a coupling period. At last time-step in a coupling period the
     656    ! fields are transformed to the grid accepted by the coupler. No
     657    ! sending to the coupler will be done from here (it is done in
     658    ! cpl_send_seaice_fields). Crucial hypothesis is that the surface
     659    ! fractions do not change between coupling time-steps.
     660
    620661    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    621662    USE indice_sol_mod
    622663    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     664    use config_ocean_skin_m, only: activate_ocean_skin
    623665
    624666! Input arguments
     
    632674    REAL, DIMENSION(klon), INTENT(IN)       :: evap, tsurf, fder, albsol
    633675    REAL, DIMENSION(klon), INTENT(IN)       :: taux, tauy, windsp
    634     REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
     676    REAL, INTENT(IN):: sens_prec_liq(:), sens_prec_sol(:) ! (knon)
    635677    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
     678   
     679    REAL, intent(in):: delta_sst(:) ! (knon)
     680    ! Ocean-air interface temperature minus bulk SST, in
     681    ! K. Defined only if activate_ocean_skin >= 1.
     682
     683    real, intent(in):: delta_sal(:) ! (knon)
     684    ! Ocean-air interface salinity minus bulk salinity, in ppt.
    636685
    637686! Local variables
     
    669718       cpl_taumod(1:knon,cpl_index) = 0.0
    670719       IF (carbon_cycle_cpl) cpl_atm_co2(1:knon,cpl_index) = 0.0
     720
     721       if (activate_ocean_skin == 2) then
     722          cpl_delta_sst = 0.
     723          cpl_delta_sal = 0.
     724       end if
    671725    ENDIF
    672726       
     
    710764!!---OB: this is correct but why knindex ??
    711765       ENDIF
     766
     767       if (activate_ocean_skin == 2) then
     768          cpl_delta_sst(ig) = cpl_delta_sst(ig) + delta_sst(ig) / REAL(nexca)
     769          cpl_delta_sal(ig) = cpl_delta_sal(ig) + delta_sal(ig) / REAL(nexca)
     770       end if
    712771     ENDDO
    713772
     
    755814             sum_error = sum_error + error
    756815          ENDIF
     816
     817          if (activate_ocean_skin == 2) then
     818             ALLOCATE(cpl_delta_sst_2D(nbp_lon, jj_nb), &
     819                  cpl_delta_sal_2D(nbp_lon, jj_nb), stat = error)
     820             sum_error = sum_error + error
     821          end if
    757822
    758823          IF (sum_error /= 0) THEN
     
    810875       IF (carbon_cycle_cpl) &
    811876            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
    812    ENDIF
     877       if (activate_ocean_skin == 2) then
     878          CALL gath2cpl(cpl_delta_sst, cpl_delta_sst_2D, knon, knindex)
     879          CALL gath2cpl(cpl_delta_sal, cpl_delta_sal_2D, knon, knindex)
     880       end if
     881    ENDIF
    813882
    814883  END SUBROUTINE cpl_send_ocean_fields
     
    846915    REAL, DIMENSION(klon), INTENT(IN)       :: albsol, taux, tauy
    847916    REAL, DIMENSION(klon,nbsrf), INTENT(IN) :: pctsrf
    848     REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
     917    REAL, INTENT(IN):: sens_prec_liq(:), sens_prec_sol(:) ! (knon)
    849918    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
    850919    LOGICAL, INTENT(IN)                     :: lafin
     
    11451214    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    11461215    USE time_phylmdz_mod, ONLY: start_time, itau_phy
     1216    use config_ocean_skin_m, only: activate_ocean_skin
    11471217! Some includes
    11481218!   
     
    12021272    tab_flds(:,:,ids_qraiic) = cpl_sens_rain2D(:,:,2)
    12031273    tab_flds(:,:,ids_qsnoic) = cpl_sens_snow2D(:,:,2)
     1274
     1275    if (activate_ocean_skin == 2) then
     1276       tab_flds(:, :, ids_delta_sst) = cpl_delta_sst_2D
     1277       tab_flds(:, :, ids_delta_sal) = cpl_delta_sal_2D
     1278    end if
    12041279   
    12051280    IF (version_ocean=='nemo') THEN
     
    14381513    ENDIF
    14391514
     1515    if (activate_ocean_skin == 2) deallocate(cpl_delta_sst_2d, cpl_delta_sal_2d)
     1516
    14401517    IF (sum_error /= 0) THEN
    14411518       abort_message='Pb in deallocation of cpl_xxxx2D coupling variables'
Note: See TracChangeset for help on using the changeset viewer.