Changeset 3627 for LMDZ6/branches
- Timestamp:
- Feb 3, 2020, 2:27:46 PM (5 years ago)
- Location:
- LMDZ6/branches/Ocean_skin/libf/phylmd
- Files:
-
- 4 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Ocean_skin/libf/phylmd/cpl_mod.F90
r3605 r3627 48 48 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: cpl_snow, cpl_evap, cpl_tsol 49 49 !$OMP THREADPRIVATE(cpl_snow,cpl_evap,cpl_tsol) 50 51 REAL, ALLOCATABLE, SAVE:: cpl_t_int(:) 52 !$OMP THREADPRIVATE(cpl_t_int) 53 50 54 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: cpl_fder, cpl_albe, cpl_taux, cpl_tauy 51 55 !$OMP THREADPRIVATE(cpl_fder,cpl_albe,cpl_taux,cpl_tauy) … … 66 70 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: read_sit ! sea ice temperature 67 71 !$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 68 77 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: read_sic ! sea ice fraction 69 78 !$OMP THREADPRIVATE(read_sic) … … 84 93 REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_snow2D, cpl_evap2D, cpl_tsol2D 85 94 !$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 86 99 REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_fder2D, cpl_albe2D 87 100 !$OMP THREADPRIVATE(cpl_fder2D, cpl_albe2D) … … 122 135 USE geometry_mod, ONLY : longitude_deg, latitude_deg, ind_cell_glo, cell_area 123 136 USE ioipsl_getin_p_mod, ONLY: getin_p 137 use config_ocean_skin_m, only: activate_ocean_skin 124 138 125 139 ! Input arguments … … 217 231 ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error) 218 232 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 219 244 ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error) 220 245 sum_error = sum_error + error … … 376 401 USE time_phylmdz_mod, ONLY: start_time, itau_phy 377 402 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 403 use config_ocean_skin_m, only: activate_ocean_skin 378 404 379 405 INCLUDE "YOMCST.h" … … 437 463 read_alb_sic(:,:) = tab_read_flds(:,:,idr_icealw) ! Albedo at sea ice 438 464 read_sit(:,:) = tab_read_flds(:,:,idr_icetem) ! Sea ice temperature 465 if (activate_ocean_skin >= 1) read_sss(:,:) = tab_read_flds(:,:,idr_sss) 439 466 !$OMP END MASTER 440 467 … … 494 521 ! 495 522 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) 497 525 ! 498 526 ! This routine returns the field for the ocean that has been read from the coupler … … 502 530 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day 503 531 USE indice_sol_mod 532 use config_ocean_skin_m, only: activate_ocean_skin 504 533 505 534 ! Input arguments … … 511 540 !************************************************************************************* 512 541 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 513 546 REAL, DIMENSION(klon), INTENT(OUT) :: u0_new 514 547 REAL, DIMENSION(klon), INTENT(OUT) :: v0_new … … 525 558 !************************************************************************************* 526 559 CALL cpl2gath(read_sst, tsurf_new, knon, knindex) 560 if (activate_ocean_skin >= 1) CALL cpl2gath(read_sss, sss, knon, knindex) 527 561 CALL cpl2gath(read_sic, sic_new, knon, knindex) 528 562 CALL cpl2gath(read_u0, u0_new, knon, knindex) … … 611 645 swdown, lwdown, fluxlat, fluxsens, & 612 646 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 620 656 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send 621 657 USE indice_sol_mod 622 658 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 659 use config_ocean_skin_m, only: activate_ocean_skin 623 660 624 661 ! Input arguments … … 634 671 REAL, DIMENSION(klon), INTENT(IN) :: sens_prec_liq, sens_prec_sol 635 672 REAL, DIMENSION(klon), INTENT(IN) :: lat_prec_liq, lat_prec_sol 673 real, intent(in):: t_int(:) ! (klon) ocean-air interface temperature, in K 636 674 637 675 ! Local variables … … 669 707 cpl_taumod(1:knon,cpl_index) = 0.0 670 708 IF (carbon_cycle_cpl) cpl_atm_co2(1:knon,cpl_index) = 0.0 709 if (activate_ocean_skin == 2) cpl_t_int(:knon) = 0. 671 710 ENDIF 672 711 … … 710 749 !!---OB: this is correct but why knindex ?? 711 750 ENDIF 751 752 if (activate_ocean_skin == 2) & 753 cpl_t_int(ig) = cpl_t_int(ig) + t_int(ig) / REAL(nexca) 712 754 ENDDO 713 755 … … 755 797 sum_error = sum_error + error 756 798 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 757 804 758 805 IF (sum_error /= 0) THEN … … 810 857 IF (carbon_cycle_cpl) & 811 858 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 813 862 814 863 END SUBROUTINE cpl_send_ocean_fields … … 1145 1194 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1146 1195 USE time_phylmdz_mod, ONLY: start_time, itau_phy 1196 use config_ocean_skin_m, only: activate_ocean_skin 1147 1197 ! Some includes 1148 1198 ! … … 1202 1252 tab_flds(:,:,ids_qraiic) = cpl_sens_rain2D(:,:,2) 1203 1253 tab_flds(:,:,ids_qsnoic) = cpl_sens_snow2D(:,:,2) 1254 if (activate_ocean_skin == 2) tab_flds(:, :, ids_t_int) = cpl_t_int_2D 1204 1255 1205 1256 IF (version_ocean=='nemo') THEN … … 1438 1489 ENDIF 1439 1490 1491 if (activate_ocean_skin == 2) deallocate(cpl_t_int_2d) 1492 1440 1493 IF (sum_error /= 0) THEN 1441 1494 abort_message='Pb in deallocation of cpl_xxxx2D coupling variables' -
LMDZ6/branches/Ocean_skin/libf/phylmd/oasis.F90
r3605 r3627 59 59 INTEGER, PARAMETER :: ids_qraiic = 28 60 60 INTEGER, PARAMETER :: ids_qsnoic = 29 61 INTEGER, PARAMETER :: maxsend = 29 ! Maximum number of fields to send 61 INTEGER, PARAMETER :: ids_t_int = 30 62 63 INTEGER, PARAMETER :: maxsend = 30 ! Maximum number of fields to send 62 64 63 65 ! Id for fields received from ocean 66 64 67 INTEGER, PARAMETER :: idr_sisutw = 1 65 68 INTEGER, PARAMETER :: idr_icecov = 2 … … 70 73 INTEGER, PARAMETER :: idr_curenz = 7 71 74 INTEGER, PARAMETER :: idr_oceco2 = 8 72 INTEGER, PARAMETER :: maxrecv = 8 ! Maximum number of fields to receive 75 76 INTEGER, PARAMETER :: idr_sss = 9 77 ! bulk salinity of the surface layer of the ocean, in ppt 78 79 INTEGER, PARAMETER :: maxrecv = 9 ! Maximum number of fields to receive 73 80 74 81 … … 183 190 infosend(ids_calvin)%action = .TRUE. ; infosend(ids_calvin)%name = 'COCALVIN' 184 191 192 if (activate_ocean_skin == 2) then 193 infosend(ids_t_int)%action = .TRUE. 194 infosend(ids_t_int)%name = 'T_int' 195 end if 196 185 197 IF (version_ocean=='nemo') THEN 186 198 infosend(ids_shftot)%action = .TRUE. ; infosend(ids_shftot)%name = 'COQSRMIX' … … 219 231 inforecv(idr_icealw)%action = .TRUE. ; inforecv(idr_icealw)%name = 'SIICEALW' 220 232 inforecv(idr_icetem)%action = .TRUE. ; inforecv(idr_icetem)%name = 'SIICTEMW' 233 234 if (activate_ocean_skin >= 1) then 235 inforecv(idr_sss)%action = .TRUE. 236 inforecv(idr_sss)%name = 'salinity' 237 end if 221 238 222 239 IF (cpl_current ) THEN -
LMDZ6/branches/Ocean_skin/libf/phylmd/ocean_cpl_mod.F90
r3463 r3627 55 55 radsol, snow, agesno, & 56 56 qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, & 57 tsurf_new, dflux_s, dflux_l )57 tsurf_new, dflux_s, dflux_l, sss) 58 58 59 59 ! … … 63 63 ! 64 64 USE dimphy, ONLY : klon 65 USE cpl_mod66 65 USE calcul_fluxs_mod 67 66 USE indice_sol_mod 68 67 USE phys_output_var_mod, ONLY : sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o 69 USE cpl_mod, ONLY : gath2cpl 68 USE cpl_mod, ONLY : gath2cpl, cpl_receive_ocean_fields, & 69 cpl_send_ocean_fields 70 70 use config_ocean_skin_m, only: activate_ocean_skin 71 71 … … 106 106 REAL, DIMENSION(klon), INTENT(OUT) :: tsurf_new 107 107 REAL, DIMENSION(klon), INTENT(OUT) :: dflux_s, dflux_l 108 109 REAL, INTENT(OUT):: sss(:) ! (klon) 110 ! bulk salinity of the surface layer of the ocean, in ppt 108 111 109 112 … … 130 133 ! 131 134 !**************************************************************************************** 132 CALL cpl_receive_ocean_fields(knon, knindex, tsurf_cpl, u0_cpl, v0_cpl) 135 CALL cpl_receive_ocean_fields(knon, knindex, tsurf_cpl, u0_cpl, v0_cpl, & 136 sss) 133 137 134 138 !**************************************************************************************** … … 156 160 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, & 157 161 sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol) 158 if (activate_ocean_skin == 2) tsurf_new = tsurf_cpl 162 163 if (activate_ocean_skin == 2) then 164 ! tsurf_new was set to tsurf_in in calcul_flux, correct it to 165 ! the new bulk SST tsurf_cpl: 166 tsurf_new = tsurf_cpl 167 end if 168 169 ! assertion: tsurf_new == tsurf_cpl 159 170 160 171 do j = 1, knon … … 197 208 swnet, lwnet, fluxlat, fluxsens, & 198 209 precip_rain, precip_snow, evap, tsurf_new, fder_new, alb1, flux_u1, flux_v1, windsp,& 199 sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol )210 sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, tsurf_in) 200 211 201 212 -
LMDZ6/branches/Ocean_skin/libf/phylmd/surf_ocean_mod.F90
r3601 r3627 57 57 REAL, DIMENSION(klon), INTENT(IN) :: rmu0 58 58 REAL, DIMENSION(klon), INTENT(IN) :: fder 59 REAL, DIMENSION(klon), INTENT(IN) :: tsurf_in59 REAL, INTENT(IN):: tsurf_in(klon) ! defined only for subscripts 1:knon 60 60 REAL, DIMENSION(klon), INTENT(IN) :: p1lay,z1lay ! pression (Pa) et altitude (m) du premier niveau 61 61 REAL, DIMENSION(klon), INTENT(IN) :: cdragh … … 102 102 REAL, DIMENSION(klon), INTENT(OUT) :: flux_u1, flux_v1 103 103 104 REAL, intent(out):: t_int(:) ! (knon) interface temperature, in K105 real, intent(out):: s_int(:) ! (knon) interface salinity, in ppt104 REAL, intent(out):: t_int(:) ! (knon) ocean-air interface temperature, in K 105 real, intent(out):: s_int(:) ! (knon) ocean-air interface salinity, in ppt 106 106 107 107 REAL, intent(out):: dter(:) ! (knon) … … 111 111 112 112 REAL, intent(out):: dser(:) ! (knon) 113 ! Temperaturevariation in the diffusive microlayer, that is114 ! subskin temperature minus ocean-air interface temperature. In K.113 ! Salinity variation in the diffusive microlayer, that is 114 ! ocean-air interface salinity minus subskin salinity. In ppt. 115 115 116 116 REAL, intent(out):: tkt(:) ! (knon) … … 140 140 real xlv(knon) ! chaleur latente d'évaporation (J / kg) 141 141 real precip_tot(knon) ! rain + snow 142 real S1(knon) ! salinity at depth_1, in ppt 142 143 real sss(klon) 144 ! Bulk salinity of the surface layer of the ocean, in ppt. (Only 145 ! defined for subscripts 1:knon, but we have to declare it with 146 ! size klon because of the coupling machinery.) 143 147 144 148 ! End definition … … 186 190 radsol, snow, agesno, & 187 191 qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, & 188 tsurf_new, dflux_s, dflux_l )192 tsurf_new, dflux_s, dflux_l, sss) 189 193 190 194 CASE('slab') … … 319 323 rf = sens_heat_rain(precip_tot, temp_air(:knon), spechum(:knon), rhoa, & 320 324 xlv, tsurf_in(:knon), ps(:knon)) 321 s1= 35.325 if (type_ocean /= 'couple') sss(:knon) = 35. 322 326 call bulk_flux(tkt, tks, taur, dter, dser, t_int, s_int, ds_ns, dt_ns, & 323 u = windsp(:knon), t_ocean_1 = tsurf_new(:knon), s1 = s 1, &327 u = windsp(:knon), t_ocean_1 = tsurf_new(:knon), s1 = sss(:knon), & 324 328 rain = precip_tot, hf = - fluxsens(:knon), hlb = - fluxlat(:knon), & 325 329 rnl = - lwnet(:knon), &
Note: See TracChangeset
for help on using the changeset viewer.