Ignore:
Timestamp:
Feb 1, 2021, 3:30:57 PM (3 years ago)
Author:
lguez
Message:

Merge Ocean_skin branch back into trunk

Location:
LMDZ6/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk

  • LMDZ6/trunk/libf/phylmd/cpl_mod.F90

    r3790 r3815  
    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
     
    218232    ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error)
    219233    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
    220245    ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error)
    221246    sum_error = sum_error + error
     
    380405    USE time_phylmdz_mod, ONLY: start_time, itau_phy
    381406    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     407    use config_ocean_skin_m, only: activate_ocean_skin
    382408
    383409    INCLUDE "YOMCST.h"
     
    441467       read_alb_sic(:,:) = tab_read_flds(:,:,idr_icealw)  ! Albedo at sea ice
    442468       read_sit(:,:)     = tab_read_flds(:,:,idr_icetem)  ! Sea ice temperature
     469       if (activate_ocean_skin >= 1) read_sss(:,:) = tab_read_flds(:,:,idr_sss)
    443470!$OMP END MASTER
    444471
     
    498525!
    499526
    500   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)
    501529!
    502530! This routine returns the field for the ocean that has been read from the coupler
     
    506534    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
    507535    USE indice_sol_mod
     536    use config_ocean_skin_m, only: activate_ocean_skin
    508537
    509538! Input arguments
     
    515544!*************************************************************************************
    516545    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
    517550    REAL, DIMENSION(klon), INTENT(OUT)      :: u0_new
    518551    REAL, DIMENSION(klon), INTENT(OUT)      :: v0_new
     
    529562!*************************************************************************************
    530563    CALL cpl2gath(read_sst, tsurf_new, knon, knindex)
     564    if (activate_ocean_skin >= 1) CALL cpl2gath(read_sss, sss, knon, knindex)
    531565    CALL cpl2gath(read_sic, sic_new, knon, knindex)
    532566    CALL cpl2gath(read_u0, u0_new, knon, knindex)
     
    615649       swdown, lwdown, fluxlat, fluxsens, &
    616650       precip_rain, precip_snow, evap, tsurf, fder, albsol, taux, tauy, windsp,&
    617        sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
    618 !
    619 ! This subroutine cumulates some fields for each time-step during a coupling
    620 ! period. At last time-step in a coupling period the fields are transformed to the
    621 ! grid accepted by the coupler. No sending to the coupler will be done from here
    622 ! (it is done in cpl_send_seaice_fields).
    623 !
     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
    624661    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    625662    USE indice_sol_mod
    626663    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     664    use config_ocean_skin_m, only: activate_ocean_skin
    627665
    628666! Input arguments
     
    636674    REAL, DIMENSION(klon), INTENT(IN)       :: evap, tsurf, fder, albsol
    637675    REAL, DIMENSION(klon), INTENT(IN)       :: taux, tauy, windsp
    638     REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
     676    REAL, INTENT(IN):: sens_prec_liq(:), sens_prec_sol(:) ! (knon)
    639677    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.
    640685
    641686! Local variables
     
    673718       cpl_taumod(1:knon,cpl_index) = 0.0
    674719       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
    675725    ENDIF
    676726       
     
    714764!!---OB: this is correct but why knindex ??
    715765       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
    716771     ENDDO
    717772
     
    759814             sum_error = sum_error + error
    760815          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
    761822
    762823          IF (sum_error /= 0) THEN
     
    814875       IF (carbon_cycle_cpl) &
    815876            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
    816    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
    817882
    818883  END SUBROUTINE cpl_send_ocean_fields
     
    850915    REAL, DIMENSION(klon), INTENT(IN)       :: albsol, taux, tauy
    851916    REAL, DIMENSION(klon,nbsrf), INTENT(IN) :: pctsrf
    852     REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
     917    REAL, INTENT(IN):: sens_prec_liq(:), sens_prec_sol(:) ! (knon)
    853918    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
    854919    LOGICAL, INTENT(IN)                     :: lafin
     
    11491214    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    11501215    USE time_phylmdz_mod, ONLY: start_time, itau_phy
     1216    use config_ocean_skin_m, only: activate_ocean_skin
    11511217! Some includes
    11521218!   
     
    12061272    tab_flds(:,:,ids_qraiic) = cpl_sens_rain2D(:,:,2)
    12071273    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
    12081279   
    12091280    IF (version_ocean=='nemo') THEN
     
    14421513    ENDIF
    14431514
     1515    if (activate_ocean_skin == 2) deallocate(cpl_delta_sst_2d, cpl_delta_sal_2d)
     1516
    14441517    IF (sum_error /= 0) THEN
    14451518       abort_message='Pb in deallocation of cpl_xxxx2D coupling variables'
Note: See TracChangeset for help on using the changeset viewer.