Changeset 522 for LMDZ.3.3/branches
- Timestamp:
- May 6, 2004, 10:57:36 AM (21 years ago)
- Location:
- LMDZ.3.3/branches/rel-LF/libf/phylmd
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ.3.3/branches/rel-LF/libf/phylmd/clmain.F
r499 r522 18 18 cIM cf JLD . zcoefh,zu1,zv1, t2m, q2m, u10m, v10m) 19 19 . zcoefh,zu1,zv1, t2m, q2m, u10m, v10m, 20 . fqcalving,ffonte )20 . fqcalving,ffonte, run_off_lic_0) 21 21 cAA . itr, tr, flux_surf, d_tr) 22 22 cAA REM: … … 101 101 REAL y_fqcalving(klon), y_ffonte(klon) 102 102 REAL fqcalving(klon,nbsrf), ffonte(klon,nbsrf) 103 REAL run_off_lic_0(klon), y_run_off_lic_0(klon) 103 104 104 105 REAL flux_u(klon,klev, nbsrf), flux_v(klon,klev, nbsrf) … … 442 443 yrads(j) = ysolsw(j)+ ysollw(j) 443 444 ypaprs(j,klev+1) = paprs(i,klev+1) 445 y_run_off_lic_0(j) = run_off_lic_0(i) 444 446 END DO 445 447 C … … 557 559 cIM cf JLD s y_flux_t, y_flux_q, y_dflux_t, y_dflux_q) 558 560 s y_flux_t, y_flux_q, y_dflux_t, y_dflux_q, 559 s y_fqcalving,y_ffonte )561 s y_fqcalving,y_ffonte,y_run_off_lic_0) 560 562 c 561 563 c calculer la longueur de rugosite sur ocean … … 635 637 END DO 636 638 END IF 639 IF ( nsrf .eq. is_lic ) THEN 640 DO j = 1, knon 641 i = ni(j) 642 run_off_lic_0(i) = y_run_off_lic_0(j) 643 END DO 644 END IF 637 645 c$$$ PB ajout pour soil 638 646 ftsoil(:,:,nsrf) = 0. … … 793 801 cIM cf JLD s flux_t, flux_q,dflux_s,dflux_l) 794 802 s flux_t, flux_q,dflux_s,dflux_l, 795 s fqcalving,ffonte )803 s fqcalving,ffonte,run_off_lic_0) 796 804 797 805 USE interface_surf … … 835 843 REAL agesno(klon) 836 844 REAL rugoro(klon) 845 REAL run_off_lic_0(klon)! runof glacier au pas de temps precedent 837 846 integer jour ! jour de l'annee en cours 838 847 real rmu0(klon) ! cosinus de l'angle solaire zenithal … … 1078 1087 s tsol_rad, tsurf_new, alb_new, alblw, emis_new, z0_new, 1079 1088 cIM cf JLD s pctsrf_new, agesno) 1080 s pctsrf_new, agesno,fqcalving,ffonte )1089 s pctsrf_new, agesno,fqcalving,ffonte, run_off_lic_0) 1081 1090 1082 1091 -
LMDZ.3.3/branches/rel-LF/libf/phylmd/conf_phys.F90
r517 r522 17 17 #include "YOMCST.inc" 18 18 !IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12 19 include "clesphys.inc"19 #include "clesphys.inc" 20 20 ! 21 21 ! Configuration de la "physique" de LMDZ a l'aide de la fonction … … 44 44 real :: fact_cldcon, facttemps,ratqsbas,ratqshaut 45 45 integer :: iflag_cldcon, if_ebil 46 46 47 ! Local 47 48 integer :: numout = 6 … … 608 609 end subroutine conf_phys 609 610 611 ! 612 !################################################################# 613 ! 614 615 subroutine conf_interface(tau_calv) 616 617 use IOIPSL 618 implicit none 619 620 ! Configuration de l'interace atm/surf 621 ! 622 ! tau_calv: temps de relaxation pour la fonte des glaciers 623 624 REAL :: tau_calv 625 626 ! Local 627 integer :: numout = 6 628 ! 629 !Config Key = tau_calv 630 !Config Desc = temps de relaxation pour fonte des glaciers en jours 631 !Config Def = 1 an 632 !Config Help = 633 ! 634 tau_calv = 360. 635 call getin('tau_calv',tau_calv) 636 637 write(numout,*)' ##############################################' 638 WRITE(numout,*)' Configuration de l''interface atm/surfaces : ' 639 WRITE(numout,*)' tau_calv = ',tau_calv 640 return 641 642 end subroutine conf_interface -
LMDZ.3.3/branches/rel-LF/libf/phylmd/interface_surf.F90
r513 r522 40 40 41 41 ! run_off ruissellement total 42 real, allocatable, dimension(:),save :: run_off42 REAL, ALLOCATABLE, DIMENSION(:),SAVE :: run_off, run_off_lic 43 43 real, allocatable, dimension(:),save :: coastalflow, riverflow 44 44 !!$PB 45 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa 45 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa,tmp_rlic 46 46 !! pour simuler la fonte des glaciers antarctiques 47 47 REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: coeff_iceberg … … 49 49 real, save :: cte_flux_iceberg = 6.3e7 50 50 integer, save :: num_antarctic = 1 51 REAL, save :: tau_calv 51 52 !!$ 52 53 CONTAINS … … 68 69 & tsol_rad, tsurf_new, alb_new, alblw, emis_new, & 69 70 !IM cf. JLD & z0_new, pctsrf_new, agesno) 70 & z0_new, pctsrf_new, agesno,fqcalving,ffonte )71 & z0_new, pctsrf_new, agesno,fqcalving,ffonte, run_off_lic_0) 71 72 72 73 … … 128 129 ! zmasq masque terre/ocean 129 130 ! rugoro rugosite orographique 131 ! run_off_lic_0 runoff glacier du pas de temps precedent 130 132 ! 131 133 ! output: … … 191 193 real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new 192 194 real, dimension(klon), intent(INOUT):: agesno 195 real, dimension(klon), intent(INOUT):: run_off_lic_0 193 196 194 197 ! Flux thermique utiliser pour fondre la neige … … 221 224 INTEGER :: isize 222 225 real, dimension(klon):: fder_prev 226 REAL, dimension(klon) :: bidule 223 227 224 228 if (check) write(*,*) 'Entree ', modname … … 228 232 ! 229 233 if (first_call) then 234 call conf_interface(tau_calv) 230 235 if (nisurf /= is_ter .and. klon > 1) then 231 236 write(*,*)' *** Warning ***' … … 306 311 call abort_gcm(modname,abort_message,1) 307 312 endif 313 ALLOCATE (tmp_rlic(iim,jjm+1), stat=error) 314 if (error /= 0) then 315 abort_message='Pb allocation tmp_rlic' 316 call abort_gcm(modname,abort_message,1) 317 endif 318 308 319 !!$ 309 320 else if (size(coastalflow) /= knon) then … … 355 366 & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, & 356 367 !IM cf JLD 357 & fqcalving,ffonte )368 & fqcalving,ffonte, run_off_lic_0) 358 369 359 370 … … 601 612 & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, & 602 613 !IM cf JLD 603 & fqcalving,ffonte )614 & fqcalving,ffonte, run_off_lic_0) 604 615 605 616 ! calcul albedo … … 655 666 if (check) write(*,*)'glacier, nisurf = ',nisurf 656 667 668 if (.not. allocated(run_off_lic)) then 669 allocate(run_off_lic(knon), stat = error) 670 if (error /= 0) then 671 abort_message='Pb allocation run_off_lic' 672 call abort_gcm(modname,abort_message,1) 673 endif 674 run_off_lic = 0. 675 endif 657 676 ! 658 677 ! Surface "glacier continentaux" appel a l'interface avec le sol … … 684 703 & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, & 685 704 !IM cf JLD 686 & fqcalving,ffonte) 687 705 & fqcalving,ffonte, run_off_lic_0) 706 707 ! passage du run-off des glaciers calcule dans fonte_neige au coupleur 708 bidule=0. 709 bidule(1:knon)= run_off_lic(1:knon) 710 call gath2cpl(bidule, tmp_rlic, klon, knon,iim,jjm,knindex) 688 711 ! 689 712 ! calcul albedo … … 1271 1294 real, allocatable, dimension(:,:),save :: cpl_snow, cpl_evap, cpl_tsol 1272 1295 real, allocatable, dimension(:,:),save :: cpl_fder, cpl_albe, cpl_taux 1273 !!$PB real, allocatable, dimension(:,:),save :: cpl_tauy, cpl_rriv, cpl_rcoa1274 1296 real, allocatable, dimension(:,:),save :: cpl_tauy 1275 real, allocatable, dimension(:,:),save :: cpl_rriv, cpl_rcoa1297 REAL, ALLOCATABLE, DIMENSION(:,:),SAVE :: cpl_rriv, cpl_rcoa, cpl_rlic 1276 1298 !!$ 1277 1299 ! variables tampons avant le passage au coupleur … … 1352 1374 allocate(cpl_taux(klon,2), stat = error); sum_error = sum_error + error 1353 1375 allocate(cpl_tauy(klon,2), stat = error); sum_error = sum_error + error 1354 !!$PB1355 !!$ allocate(cpl_rcoa(klon,2), stat = error); sum_error = sum_error + error1356 !!$ allocate(cpl_rriv(klon,2), stat = error); sum_error = sum_error + error1357 1376 ALLOCATE(cpl_rriv(iim,jjm+1), stat=error); sum_error = sum_error + error 1358 1377 ALLOCATE(cpl_rcoa(iim,jjm+1), stat=error); sum_error = sum_error + error 1378 ALLOCATE(cpl_rlic(iim,jjm+1), stat=error); sum_error = sum_error + error 1359 1379 !! 1360 1380 allocate(read_sst(iim, jjm+1), stat = error); sum_error = sum_error + error … … 1369 1389 cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0. 1370 1390 cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0. 1371 cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0. 1391 cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.; cpl_rlic = 0. 1372 1392 1373 1393 sum_error = 0 … … 1471 1491 cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) & 1472 1492 & + tauy(ig) / FLOAT(nexca) 1473 !!$ cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &1474 !!$ & + riverflow(ig) / FLOAT(nexca)/dtime1475 !!$ cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &1476 !!$ & + coastalflow(ig) / FLOAT(nexca)/dtime1477 1493 enddo 1478 1494 IF (cpl_index .EQ. 1) THEN 1479 1495 cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca) 1480 1496 cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca) 1497 cpl_rlic(:,:) = cpl_rlic(:,:) + tmp_rlic(:,:) / FLOAT(nexca) 1481 1498 ENDIF 1482 1499 endif … … 1600 1617 call gath2cpl(cpl_taux(1,cpl_index), tmp_taux(1,1,cpl_index), klon, knon,iim,jjm, knindex) 1601 1618 call gath2cpl(cpl_tauy(1,cpl_index), tmp_tauy(1,1,cpl_index), klon, knon,iim,jjm, knindex) 1602 !!$ call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm, knindex)1603 !!$ call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm, knindex)1604 1619 1605 1620 ! … … 1622 1637 wri_rriv = cpl_rriv(:,:) 1623 1638 wri_rcoa = cpl_rcoa(:,:) 1639 DO j = 1, jjm + 1 1640 wri_calv(:,j) = sum(cpl_rlic(:,j)) / iim 1641 enddo 1624 1642 1625 1643 where (tamp_zmasq /= 1.) … … 1629 1647 wri_snow = tmp_snow(:,:,1) * tamp_srf(:,:,1) / deno + & 1630 1648 & tmp_snow(:,:,2) * tamp_srf(:,:,2) / deno 1631 !!$PB1632 !!$ wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno + &1633 !!$ & tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno1634 !!$ wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno + &1635 !!$ & tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno1636 1649 wri_taux = tmp_taux(:,:,1) * tamp_srf(:,:,1) / deno + & 1637 1650 & tmp_taux(:,:,2) * tamp_srf(:,:,2) / deno … … 1644 1657 !$$$ wri_rain = wri_rain & 1645 1658 !$$$ & + coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille) 1646 wri_calv = coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille)1659 ! wri_calv = coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille) 1647 1660 ! 1648 1661 ! on passe les coordonnées de la grille … … 1701 1714 cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0. 1702 1715 cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0. 1703 cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0. 1716 cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.; cpl_rlic = 0. 1704 1717 ! 1705 1718 ! deallocation memoire variables temporaires … … 2542 2555 & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, & 2543 2556 !IM cf JLD 2544 & fqcalving,ffonte )2557 & fqcalving,ffonte,run_off_lic_0) 2545 2558 2546 2559 ! Routine de traitement de la fonte de la neige dans le cas du traitement … … 2575 2588 ! dflux_s derivee du flux de chaleur sensible / Ts 2576 2589 ! dflux_l derivee du flux de chaleur latente / Ts 2590 ! in/out: 2591 ! run_off_lic_0 run off glacier du pas de temps précedent 2577 2592 ! 2578 2593 … … 2581 2596 #include "indicesol.inc" 2582 2597 !IM cf JLD 2583 !#include "YOMCST.inc"2598 #include "YOMCST.inc" 2584 2599 2585 2600 ! Parametres d'entree … … 2603 2618 ! hauteur de neige, en kg/m2/s 2604 2619 real, dimension(klon), intent(INOUT):: fqcalving 2605 2620 real, dimension(klon), intent(INOUT):: run_off_lic_0 2606 2621 ! Variables locales 2607 2622 ! Masse maximum de neige (kg/m2). Au dessus de ce seuil, la neige … … 2619 2634 real :: bilan_f, fq_fonte 2620 2635 REAL :: subli, fsno 2621 real, dimension(klon) :: bil_eau_s2636 REAL, DIMENSION(klon) :: bil_eau_s, snow_evap 2622 2637 real, parameter :: t_grnd = 271.35, t_coup = 273.15 2623 2638 !! PB temporaire en attendant mieux pour le modele de neige … … 2634 2649 character (len = 80) :: abort_message 2635 2650 logical,save :: first = .true.,second=.false. 2651 real :: coeff_rel 2652 2636 2653 2637 2654 if (check) write(*,*)'Entree ', modname,' surface = ',nisurf 2638 2655 2639 2656 ! Initialisations 2657 coeff_rel = dtime/(tau_calv * rday) 2640 2658 bil_eau_s(:) = 0. 2641 2659 DO i = 1, knon … … 2699 2717 2700 2718 WHERE (precip_snow > 0.) snow = snow + (precip_snow * dtime) 2701 WHERE (evap > 0 ) snow = MAX(0.0, snow - (evap * dtime)) 2702 bil_eau_s = bil_eau_s + (precip_rain - evap) * dtime 2719 snow_evap = 0. 2720 WHERE (evap > 0. ) 2721 snow_evap = MIN (snow / dtime, evap) 2722 snow = snow - snow_evap * dtime 2723 snow = MAX(0.0, snow) 2724 end where 2725 2726 ! bil_eau_s = bil_eau_s + (precip_rain * dtime) - (evap - snow_evap) * dtime 2727 bil_eau_s = (precip_rain * dtime) - (evap - snow_evap) * dtime 2728 2703 2729 ! 2704 2730 ! Y'a-t-il fonte de neige? … … 2716 2742 !IM cf JLD OK 2717 2743 !IM cf JLD/ GKtest fonte aussi pour la glace 2718 ! IF (nisurf == is_sic .OR. nisurf == is_lic ) tsurf_new(i) = RTT2719 2744 IF (nisurf == is_sic .OR. nisurf == is_lic ) THEN 2720 2745 fq_fonte = MAX((tsurf_new(i)-RTT )/chaice,0.0) … … 2723 2748 tsurf_new(i) = RTT 2724 2749 ENDIF 2725 ! fin GKtest2726 2750 d_ts(i) = tsurf_new(i) - tsurf(i) 2727 ! zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)2728 ! zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)2729 !== flux_q est le flux de vapeur d'eau: kg/(m**2 s) positive vers bas2730 !== flux_t est le flux de cpt (energie sensible): j/(m**2 s)2731 !!$ evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)2732 !!$ fluxlat(i) = - evap(i) * zx_sl(i)2733 !!$ fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)2734 ! Derives des flux dF/dTs (W m-2 K-1):2735 !!$ dflux_s(i) = zx_nh(i)2736 !!$ dflux_l(i) = (zx_sl(i) * zx_nq(i))2737 !!$ bilan_f = radsol(i) + fluxsens(i) - (zx_sl(i) * evap (i)) - &2738 !!$ & dif_grnd(i) * (tsurf_new(i) - t_grnd) - &2739 !!$ & RCPD * (zx_pkh(i))/cal(i)/dtime * (tsurf_new(i) - tsurf(i))2740 !!$ bilan_f = max(0., bilan_f)2741 !!$ fq_fonte = bilan_f / zx_sl(i)2742 2751 endif 2743 2752 ! … … 2750 2759 run_off(i) = run_off(i) + MAX(qsol(i) - max_eau_sol, 0.0) 2751 2760 qsol(i) = MIN(qsol(i), max_eau_sol) 2752 !IM : 0601003 else 2753 !IM: run_off(i) 2754 !IM : 061003 run_off(i) = run_off(i) + MAX(bil_eau_s(i), 0.0) 2761 else if (nisurf == is_lic) then 2762 run_off_lic(i) = (coeff_rel * fqcalving(i)) + & 2763 & (1. - coeff_rel) * run_off_lic_0(i) 2764 run_off_lic_0(i) = run_off_lic(i) 2765 run_off_lic(i) = run_off_lic(i) + bil_eau_s(i)/dtime 2755 2766 endif 2756 2767 enddo -
LMDZ.3.3/branches/rel-LF/libf/phylmd/phyetat0.F
r467 r522 7 7 . fder,radsol,frugs,agesno,clesphy0, 8 8 . zmea,zstd,zsig,zgam,zthe,zpic,zval,rugsrel,tabcntr0, 9 . t_ancien,q_ancien,ancien_ok, rnebcon, ratqs,clwcon) 9 . t_ancien,q_ancien,ancien_ok, rnebcon, ratqs,clwcon, 10 . run_off_lic_0) 10 11 IMPLICIT none 11 12 c====================================================================== … … 56 57 REAL pctsrf(klon, nbsrf) 57 58 REAL fractint(klon) 59 REAL run_off_lic_0(klon) 58 60 59 61 REAL t_ancien(klon,klev), q_ancien(klon,klev) … … 1333 1335 ENDIF 1334 1336 c 1337 c Lecture ratqs 1338 c 1335 1339 ierr = NF_INQ_VARID (nid, "RATQS", nvarid) 1336 1340 IF (ierr.NE.NF_NOERR) THEN … … 1355 1359 PRINT*,'(ecart-type) ratqs:', xmin, xmax 1356 1360 c 1361 c Lecture run_off_lic_0 1362 c 1363 ierr = NF_INQ_VARID (nid, "RUNOFFLIC0", nvarid) 1364 IF (ierr.NE.NF_NOERR) THEN 1365 PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent" 1366 PRINT*, "Depart legerement fausse. Mais je continue" 1367 run_off_lic_0 = 0. 1368 ELSE 1369 #ifdef NC_DOUBLE 1370 ierr = NF_GET_VAR_DOUBLE(nid, nvarid, run_off_lic_0) 1371 #else 1372 ierr = NF_GET_VAR_REAL(nid, nvarid, run_off_lic_0) 1373 #endif 1374 IF (ierr.NE.NF_NOERR) THEN 1375 PRINT*, "phyetat0: Lecture echouee pour <RUNOFFLIC0>" 1376 CALL abort 1377 ENDIF 1378 ENDIF 1379 xmin = 1.0E+20 1380 xmax = -1.0E+20 1381 xmin = MINval(run_off_lic_0) 1382 xmax = MAXval(run_off_lic_0) 1383 PRINT*,'(ecart-type) run_off_lic_0:', xmin, xmax 1384 c 1357 1385 c Fermer le fichier: 1358 1386 c -
LMDZ.3.3/branches/rel-LF/libf/phylmd/phyredem.F
r467 r522 8 8 . radsol,frugs,agesno, 9 9 . zmea,zstd,zsig,zgam,zthe,zpic,zval,rugsrel, 10 . t_ancien, q_ancien, rnebcon, ratqs, clwcon) 10 . t_ancien, q_ancien, rnebcon, ratqs, clwcon, 11 . run_off_lic_0) 11 12 IMPLICIT none 12 13 c====================================================================== … … 59 60 REAL t_ancien(klon,klev), q_ancien(klon,klev) 60 61 real clwcon(klon,klev),rnebcon(klon,klev),ratqs(klon,klev) 62 REAL run_off_lic_0(klon) 61 63 c 62 64 INTEGER nid, nvarid, idim1, idim2, idim3 … … 759 761 #endif 760 762 c 763 c run_off_lic_0 764 c 765 ierr = NF_REDEF (nid) 766 #ifdef NC_DOUBLE 767 ierr=NF_DEF_VAR(nid,"RUNOFFLIC0",NF_DOUBLE,1,idim2,nvarid) 768 #else 769 ierr=NF_DEF_VAR(nid,"RUNOFFLIC0",NF_FLOAT, 1,idim2,nvarid) 770 #endif 771 ierr = NF_PUT_ATT_TEXT (nid,nvarid,"title", 28, 772 . "Runofflic0") 773 ierr = NF_ENDDEF(nid) 774 #ifdef NC_DOUBLE 775 ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,run_off_lic_0) 776 #else 777 ierr = NF_PUT_VAR_REAL (nid,nvarid,run_off_lic_0) 778 #endif 779 c 761 780 c 762 781 ierr = NF_CLOSE(nid) -
LMDZ.3.3/branches/rel-LF/libf/phylmd/physiq.F
r521 r522 535 535 REAL alb_neig(klon) 536 536 SAVE alb_neig ! albedo de la neige 537 c 538 REAL run_off_lic_0(klon) 539 SAVE run_off_lic_0 537 540 cKE43 538 541 c Variables liees a la convection de K. Emanuel (sb): … … 1041 1044 . dlw,radsol,frugs,agesno,clesphy0, 1042 1045 . zmea,zstd,zsig,zgam,zthe,zpic,zval,rugoro,tabcntr0, 1043 . t_ancien, q_ancien, ancien_ok, rnebcon, ratqs,clwcon ) 1046 . t_ancien, q_ancien, ancien_ok, rnebcon, ratqs,clwcon, 1047 . run_off_lic_0) 1044 1048 1045 1049 c … … 1453 1457 s dsens, devap, 1454 1458 s ycoefh,yu1,yv1, t2m, q2m, u10m, v10m, 1455 s fqcalving, ffonte)1459 s fqcalving, ffonte, run_off_lic_0) 1456 1460 c 1457 1461 CXXX PB … … 2760 2764 . radsol,frugs,agesno, 2761 2765 . zmea,zstd,zsig,zgam,zthe,zpic,zval,rugoro, 2762 . t_ancien, q_ancien, rnebcon, ratqs, clwcon )2766 . t_ancien, q_ancien, rnebcon, ratqs, clwcon,run_off_lic_0) 2763 2767 ENDIF 2764 2768
Note: See TracChangeset
for help on using the changeset viewer.