--- trunk/phylmd/Interface_surf/interfsurf_hq.f 2018/07/26 16:02:11 297 +++ trunk/phylmd/Interface_surf/interfsurf_hq.f 2018/09/11 11:08:38 305 @@ -4,12 +4,12 @@ contains - SUBROUTINE interfsurf_hq(dtime, julien, rmu0, nisurf, knindex, debut, & - tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, tq_cdrag, petAcoef, & - peqAcoef, petBcoef, peqBcoef, precip_rain, precip_snow, rugos, rugoro, & - snow, qsurf, ts, p1lay, ps, radsol, evap, flux_t, fluxlat, dflux_l, & - dflux_s, tsurf_new, albedo, z0_new, pctsrf_new_sic, agesno, fqcalving, & - ffonte, run_off_lic_0) + SUBROUTINE interfsurf_hq(julien, mu0, nisurf, knindex, tsoil, qsol, u1_lay, & + v1_lay, temp_air, spechum, tq_cdrag, tAcoef, qAcoef, tBcoef, qBcoef, & + rain_fall, snow_fall, rugos, rugoro, snow, qsurf, ts, p1lay, ps, & + radsol, evap, flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, & + z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0, & + run_off_lic) ! Cette routine sert d'aiguillage entre l'atmosph\`ere et la surface ! en g\'en\'eral (sols continentaux, oc\'eans, glaces) pour les flux de @@ -21,26 +21,20 @@ use alboc_cd_m, only: alboc_cd USE albsno_m, ONLY: albsno USE calcul_fluxs_m, ONLY: calcul_fluxs - USE dimphy, ONLY: klon USE fonte_neige_m, ONLY: fonte_neige USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter - USE conf_interface_m, ONLY: conf_interface USE interfsur_lim_m, ONLY: interfsur_lim use limit_read_sst_m, only: limit_read_sst use soil_m, only: soil USE suphec_m, ONLY: rcpd, rtt - real, intent(IN):: dtime ! pas de temps de la physique (en s) integer, intent(IN):: julien ! jour dans l'annee en cours - real, intent(IN):: rmu0(klon) ! cosinus de l'angle solaire zenithal + real, intent(IN):: mu0(:) ! (knon) cosinus de l'angle solaire zenithal integer, intent(IN):: nisurf ! index de la surface a traiter integer, intent(in):: knindex(:) ! (knon) ! index des points de la surface a traiter - logical, intent(IN):: debut ! 1er appel a la physique - ! (si false calcul simplifie des fluxs sur les continents) - REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx) REAL, intent(INOUT):: qsol(:) ! (knon) @@ -52,16 +46,16 @@ real, intent(IN):: spechum(:) ! (knon) humidite specifique 1ere couche real, intent(IN):: tq_cdrag(:) ! (knon) coefficient d'echange - real, intent(IN):: petAcoef(:), peqAcoef(:) ! (knon) + real, intent(IN):: tAcoef(:), qAcoef(:) ! (knon) ! coefficients A de la r\'esolution de la couche limite pour t et q - real, intent(IN):: petBcoef(:), peqBcoef(:) ! (knon) + real, intent(IN):: tBcoef(:), qBcoef(:) ! (knon) ! coefficients B de la r\'esolution de la couche limite pour t et q - real, intent(IN):: precip_rain(klon) + real, intent(IN):: rain_fall(:) ! (knon) ! precipitation, liquid water mass flux (kg / m2 / s), positive down - real, intent(IN):: precip_snow(klon) + real, intent(IN):: snow_fall(:) ! (knon) ! precipitation, solid water mass flux (kg / m2 / s), positive down real, intent(IN):: rugos(:) ! (knon) rugosite @@ -83,7 +77,7 @@ real, intent(OUT):: albedo(:) ! (knon) albedo real, intent(OUT):: z0_new(:) ! (knon) surface roughness - real, intent(in):: pctsrf_new_sic(:) ! (klon) + real, intent(in):: pctsrf_new_sic(:) ! (knon) ! nouvelle repartition des surfaces real, intent(INOUT):: agesno(:) ! (knon) @@ -92,21 +86,20 @@ ! Flux d'eau "perdue" par la surface et n\'ecessaire pour limiter la ! hauteur de neige, en kg / m2 / s - real, dimension(klon), intent(INOUT):: ffonte - ! Flux thermique utiliser pour fondre la neige + real, intent(OUT):: ffonte(:) ! (knon) + ! flux thermique utilis\'e pour fondre la neige - real, dimension(klon), intent(INOUT):: run_off_lic_0 + real, intent(INOUT):: run_off_lic_0(:) ! (knon) ! run_off_lic_0 runoff glacier du pas de temps precedent + REAL, intent(OUT):: run_off_lic(:) ! (knon) ruissellement total + ! Local: - integer knon ! nombre de points de la surface a traiter REAL soilcap(size(knindex)) ! (knon) REAL soilflux(size(knindex)) ! (knon) - logical:: first_call = .true. integer ii real cal(size(knindex)) ! (knon) real beta(size(knindex)) ! (knon) evap reelle - real dif_grnd(klon) real tsurf(size(knindex)) ! (knon) real alb_neig(size(knindex)) ! (knon) real zfra(size(knindex)) ! (knon) @@ -116,37 +109,6 @@ !------------------------------------------------------------- - knon = size(knindex) - - ! On doit commencer par appeler les schemas de surfaces continentales - ! car l'ocean a besoin du ruissellement qui est y calcule - - if (first_call) then - call conf_interface - - if (nisurf /= is_ter .and. klon > 1) then - print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter - print *, 'or on doit commencer par les surfaces continentales' - call abort_gcm("interfsurf_hq", & - 'On doit commencer par les surfaces continentales') - endif - - if (is_oce > is_sic) then - print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic - call abort_gcm("interfsurf_hq", & - "L'ocean doit etre traite avant la banquise") - endif - - first_call = .false. - endif - - ! Initialisations diverses - - ffonte(1:knon) = 0. - dif_grnd = 999999. - - ! Aiguillage vers les differents schemas de surface - select case (nisurf) case (is_ter) ! Surface "terre", appel \`a l'interface avec les sols continentaux @@ -156,22 +118,20 @@ ! Read albedo from the file containing boundary conditions then ! add the albedo of snow: - call interfsur_lim(dtime, julien, knindex, debut, albedo, z0_new) + call interfsur_lim(julien, knindex, albedo, z0_new) beta = min(2. * qsol / max_eau_sol, 1.) - dif_grnd(:knon) = 0. - CALL soil(dtime, is_ter, snow, ts, tsoil, soilcap, soilflux) + CALL soil(is_ter, snow, ts, tsoil, soilcap, soilflux) cal = RCPD / soilcap - CALL calcul_fluxs(dtime, ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, & - radsol + soilflux, dif_grnd(:knon), temp_air, spechum, u1_lay, & - v1_lay, petAcoef, peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, & - fluxlat, flux_t, dflux_s, dflux_l) - CALL fonte_neige(is_ter, dtime, precip_rain(:knon), precip_snow(:knon), & - snow, qsol, tsurf_new, evap, fqcalving, ffonte(:knon), & - run_off_lic_0(:knon)) + CALL calcul_fluxs(ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, & + radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, & + qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, & + dflux_l, dif_grnd = 0.) + CALL fonte_neige(is_ter, rain_fall, snow_fall, snow, qsol, & + tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic) - call albsno(dtime, agesno, alb_neig, precip_snow(:knon)) + call albsno(agesno, alb_neig, snow_fall) where (snow < 0.0001) agesno = 0. zfra = max(0., min(1., snow / (snow + 10.))) albedo = alb_neig * zfra + albedo * (1. - zfra) @@ -179,23 +139,22 @@ case (is_oce) ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean + ffonte = 0. call limit_read_sst(julien, knindex, tsurf) cal = 0. beta = 1. - dif_grnd = 0. - call calcul_fluxs(dtime, tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, & - radsol, dif_grnd(:knon), temp_air, spechum, u1_lay, v1_lay, & - petAcoef, peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, fluxlat, & - flux_t, dflux_s, dflux_l) + call calcul_fluxs(tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, radsol, & + temp_air, spechum, u1_lay, v1_lay, tAcoef, qAcoef, tBcoef, qBcoef, & + tsurf_new, evap, fluxlat, flux_t, dflux_s, dflux_l, dif_grnd = 0.) agesno = 0. - albedo = alboc_cd(rmu0(knindex)) * fmagic + albedo = alboc_cd(mu0) * fmagic z0_new = sqrt(rugos**2 + rugoro**2) fqcalving = 0. case (is_sic) ! Surface "glace de mer" appel a l'interface avec l'ocean - DO ii = 1, knon - IF (pctsrf_new_sic(knindex(ii)) < EPSFRA) then + DO ii = 1, size(knindex) + IF (pctsrf_new_sic(ii) < EPSFRA) then snow(ii) = 0. tsurf_new(ii) = RTT - 1.8 tsoil(ii, :) = RTT - 1.8 @@ -204,23 +163,20 @@ endif enddo - CALL soil(dtime, is_sic, snow, tsurf_new, tsoil, soilcap, soilflux) + CALL soil(is_sic, snow, tsurf_new, tsoil, soilcap, soilflux) cal = RCPD / soilcap - dif_grnd = 1. / tau_gl tsurf = tsurf_new beta = 1. - - CALL calcul_fluxs(dtime, tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, & - radsol + soilflux, dif_grnd(:knon), temp_air, spechum, u1_lay, & - v1_lay, petAcoef, peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, & - fluxlat, flux_t, dflux_s, dflux_l) - CALL fonte_neige(is_sic, dtime, precip_rain(:knon), & - precip_snow(:knon), snow, qsol, tsurf_new, evap, & - fqcalving, ffonte(:knon), run_off_lic_0(:knon)) + CALL calcul_fluxs(tsurf, p1lay, cal, beta, tq_cdrag, ps, qsurf, & + radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, & + qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, & + dflux_l, dif_grnd = 1. / tau_gl) + CALL fonte_neige(is_sic, rain_fall, snow_fall, snow, qsol, & + tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic) ! Compute the albedo: - CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon)) + CALL albsno(agesno, alb_neig, snow_fall) WHERE (snow < 0.0001) agesno = 0. zfra = MAX(0., MIN(1., snow / (snow + 10.))) albedo = alb_neig * zfra + 0.6 * (1. - zfra) @@ -229,21 +185,18 @@ case (is_lic) ! Surface "glacier continentaux" appel a l'interface avec le sol - CALL soil(dtime, is_lic, snow, ts, tsoil, soilcap, soilflux) + CALL soil(is_lic, snow, ts, tsoil, soilcap, soilflux) cal = RCPD / soilcap beta = 1. - dif_grnd = 0. - - call calcul_fluxs(dtime, ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, & - radsol + soilflux, dif_grnd(:knon), temp_air, spechum, u1_lay, & - v1_lay, petAcoef, peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, & - fluxlat, flux_t, dflux_s, dflux_l) - call fonte_neige(is_lic, dtime, precip_rain(:knon), & - precip_snow(:knon), snow, qsol, tsurf_new, evap, & - fqcalving, ffonte(:knon), run_off_lic_0(:knon)) + call calcul_fluxs(ts, p1lay, cal, beta, tq_cdrag, ps, qsurf, & + radsol + soilflux, temp_air, spechum, u1_lay, v1_lay, tAcoef, & + qAcoef, tBcoef, qBcoef, tsurf_new, evap, fluxlat, flux_t, dflux_s, & + dflux_l, dif_grnd = 0.) + call fonte_neige(is_lic, rain_fall, snow_fall, snow, qsol, & + tsurf_new, evap, fqcalving, ffonte, run_off_lic_0, run_off_lic) ! calcul albedo - CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon)) + CALL albsno(agesno, alb_neig, snow_fall) WHERE (snow < 0.0001) agesno = 0. albedo = 0.77