Changeset 686
- Timestamp:
- Apr 4, 2006, 5:02:07 PM (19 years ago)
- Location:
- LMDZ4/trunk/libf/phylmd
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ4/trunk/libf/phylmd/clmain.F
r674 r686 130 130 REAL tslab(klon), ytslab(klon) 131 131 REAL seaice(klon), y_seaice(klon) 132 c 133 REAL amn, amx 132 134 cIM cf JLD 133 135 REAL y_fqcalving(klon), y_ffonte(klon) … … 506 508 c PRINT *, 'tslab = ', i, tslab(i) 507 509 ytslab(i) = tslab(i) 510 y_seaice(i) = seaice(i) 508 511 c 509 512 ysnow(j) = snow(i,nsrf) … … 976 979 c 977 980 IF(OCEAN.EQ.'slab ') THEN 978 IF(nsrf.EQ.is_oce) then 981 cIM appel interfoce_slab sur is_oce IF(nsrf.EQ.is_oce) then 982 cIM appel interfoce_slab sur is_sic 983 IF(nsrf.EQ.is_sic) then !appel sic 979 984 tslab(1:klon) = ytslab(1:klon) 980 985 seaice(1:klon) = y_seaice(1:klon) -
LMDZ4/trunk/libf/phylmd/interface_surf.F90
r644 r686 39 39 #include "YOMCST.inc" 40 40 #include "indicesol.inc" 41 41 !IM 42 #include "clesphys.inc" 42 43 43 44 ! run_off ruissellement total … … 185 186 real, dimension(klon), intent(IN) :: tsurf, p1lay 186 187 !IM: "slab" ocean 188 real :: amn, amx 187 189 real, dimension(klon), intent(INOUT) :: tslab 188 190 real, allocatable, dimension(:), save :: tmp_tslab 189 191 real, dimension(klon), intent(OUT) :: flux_o, flux_g 190 192 real, dimension(klon), intent(INOUT) :: seaice ! glace de mer (kg/m2) 193 real, dimension(klon) :: siceh ! hauteur glace de mer (m) 191 194 REAL, DIMENSION(klon), INTENT(INOUT) :: radsol,fder 192 195 real, dimension(klon), intent(IN) :: zmasq … … 255 258 real, dimension(klon):: fder_prev 256 259 REAL, dimension(klon) :: bidule 260 ! 261 !IM ?? quelques variables pour netcdf 262 #include "netcdf.inc" 257 263 258 264 if (check) write(*,*) 'Entree ', modname … … 339 345 endif 340 346 endif 341 DO i=1, knon342 tmp_radsol(knindex(i))=radsol(i)343 ENDDO344 347 if (.not. allocated(tmp_pctsrf_slab)) then 345 348 allocate(tmp_pctsrf_slab(klon,nbsrf), stat = error) … … 359 362 call abort_gcm(modname,abort_message,1) 360 363 endif 361 DO i=1, klon362 tmp_seaice(i)=seaice(i)363 END DO364 IF(check) THEN 365 PRINT*,'allocation tmp_seaice nisurf itime',nisurf, itime 366 ENDIF 364 367 endif 365 368 ! … … 515 518 else if (nisurf == is_oce) then 516 519 517 if (check) write(*,*)'ocean, nisurf = ',nisurf 518 519 520 if (check) write(*,*)'ocean, nisurf = ',nisurf,'knon=',knon 520 521 ! 521 522 ! Surface "ocean" appel a l'interface avec l'ocean … … 555 556 !IM: "slab" ocean 556 557 else if (ocean == 'slab ') then 557 tsurf_new = tsurf 558 DO i=1, knon 559 tsurf_new(i) = tmp_tslab(knindex(i)) 560 ENDDO 558 561 pctsrf_new = tmp_pctsrf_slab 559 562 ! … … 599 602 zx_sl(i) = RLVTT 600 603 if (tsurf_new(i) .LT. RTT) zx_sl(i) = RLSTT 601 flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i) 604 !IM flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i) 605 flux_o(i) = fluxsens(i) + fluxlat(i) 602 606 tmp_flux_o(knindex(i)) = flux_o(i) 603 607 tmp_radsol(knindex(i))=radsol(i) … … 623 627 & pctsrf_new) 624 628 625 !IM: "slab" ocean626 else if (ocean == 'slab ') then627 !628 seaice=tmp_seaice629 cumul = .true.630 call interfoce(klon, debut, itime, dtime, jour, &631 & tmp_radsol, tmp_flux_o, tmp_flux_g, pctsrf, &632 & tslab, seaice, pctsrf_new)633 !634 tmp_pctsrf_slab=pctsrf_new635 DO i=1, knon636 tsurf_new(i)=tslab(knindex(i))637 ENDDO !i638 !639 629 endif 640 630 … … 658 648 else if (nisurf == is_sic) then 659 649 660 if (check) write(*,*)'sea ice, nisurf = ',nisurf 661 650 if (check) write(*,*)'sea ice, nisurf = ',nisurf,'knon=',knon 662 651 ! 663 652 ! Surface "glace de mer" appel a l'interface avec l'ocean … … 697 686 !IM: "slab" ocean 698 687 else if (ocean == 'slab ') then 688 !IM ajout sicOBSERVE BEG 689 IF ( ok_slab_sicOBS) THEN 690 ! ! lecture conditions limites 691 CALL interfoce(itime, dtime, jour, & 692 & klon, nisurf, knon, knindex, & 693 & debut, & 694 & tsurf_new, pctsrf_new) 695 ! 696 tmp_pctsrf_slab=pctsrf_new 697 print*,'jour lecture pctsrf_new sic =',jour 698 ! 699 ELSE !ok_slab_sicOBS 699 700 pctsrf_new=tmp_pctsrf_slab 701 ENDIF 702 !IM ajout sicOBSERVE END 700 703 ! 701 704 DO ii = 1, knon … … 732 735 DO ii = 1, knon 733 736 tsurf_new(ii) = tsurf(ii) 734 !IMbad IF (pctsrf_new(ii,nisurf) < EPSFRA) then735 737 IF (pctsrf_new(knindex(ii),nisurf) < EPSFRA) then 736 738 snow(ii) = 0.0 … … 748 750 cal(1:knon) = RCPD / soilcap(1:knon) 749 751 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon) 750 dif_grnd = 0.752 dif_grnd = 1.0 / tau_gl 751 753 ELSE 752 754 dif_grnd = 1.0 / tau_gl … … 757 759 tsurf_temp = tsurf_new 758 760 beta = 1.0 759 ENDIF 761 ENDIF !ocean == 760 762 761 763 CALL calcul_fluxs( klon, knon, nisurf, dtime, & … … 766 768 & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l) 767 769 ! 768 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean769 DO i = 1, knon770 flux_g(i) = 0.0771 !772 !IM: faire dependre le coefficient de conduction de la glace de mer773 ! de l'epaisseur de la glace de mer, dans l'hypothese ou le coeff.774 ! actuel correspond a 3m de glace de mer, cf. L.Li775 !776 ! IF(1.EQ.0) THEN777 ! IF(siceh(i).GT.0.) THEN778 ! new_dif_grnd(i) = dif_grnd(i)*3./siceh(i)779 ! ELSE780 ! new_dif_grnd(i) = 0.781 ! ENDIF782 ! ENDIF !(1.EQ.0) THEN783 !784 IF (cal(i).GT.1.0e-15) flux_g(i)=(tsurf_new(i)-t_grnd) &785 & * dif_grnd(i) *RCPD/cal(i)786 ! & * new_dif_grnd(i) *RCPD/cal(i)787 tmp_flux_g(knindex(i))=flux_g(i)788 tmp_radsol(knindex(i))=radsol(i)789 ENDDO790 791 770 IF (ocean /= 'couple') THEN 792 771 CALL fonte_neige( klon, knon, nisurf, dtime, & … … 807 786 !! alb_new(1 : knon) = 0.6 808 787 ENDIF 788 ! 789 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean 790 ! 791 DO i = 1, knon 792 ! 793 !IM: faire dependre le coefficient de conduction de la glace de mer 794 ! de l'epaisseur de la glace de mer, dans l'hypothese ou le coeff. 795 ! actuel correspond a 3m de glace de mer, cf. L.Li 796 ! 797 IF(1.EQ.0) THEN 798 IF(siceh(i).GT.0.) THEN 799 new_dif_grnd(i) = dif_grnd(i)*3./siceh(i) 800 ELSE 801 new_dif_grnd(i) = 0. 802 ENDIF 803 ENDIF !(1.EQ.0) THEN 804 ! 805 IF (cal(i).GT.1.0e-15) THEN 806 flux_g(i)=(tsurf_new(i)-t_grnd) & 807 & * dif_grnd(i) *RCPD/cal(i) 808 ! & * new_dif_grnd(i) *RCPD/cal(i) 809 ENDIF 810 tmp_flux_g(knindex(i))=flux_g(i) 811 ! 812 !IM: Attention: ne pas initialiser le tmp_radsol puisque c'est deja fait sur is_oce; 813 !IM: tmp_radsol doit etre le flux solaire qui arrive sur l'ocean 814 !IM: et non pas celui qui arrive sur la glace de mer 815 ! 816 ENDDO 809 817 810 818 fder_prev = fder … … 841 849 & pctsrf_new) 842 850 843 ! else if (ocean == 'slab ') then 844 ! call interfoce(nisurf) 851 !IM: "slab" ocean 852 else if (ocean == 'slab ') then 853 ! 854 IF (check) THEN 855 amn=MIN(tmp_tslab(1),1000.) 856 amx=MAX(tmp_tslab(1),-1000.) 857 DO i=2, klon 858 amn=MIN(tmp_tslab(i),amn) 859 amx=MAX(tmp_tslab(i),amx) 860 ENDDO 861 ! 862 PRINT*,' debut avant interfoce_slab min max tmp_tslab',amn,amx 863 ENDIF !(check) THEN 864 ! 865 cumul = .true. 866 tslab = tmp_tslab 867 call interfoce(klon, debut, itime, dtime, jour, & 868 & tmp_radsol, tmp_flux_o, tmp_flux_g, tmp_pctsrf_slab, & 869 & tslab, seaice, pctsrf_new) 870 ! 871 tmp_seaice=seaice 872 tmp_pctsrf_slab=pctsrf_new 873 DO i=1, knon 874 tmp_tslab(knindex(i))=tslab(knindex(i)) 875 ENDDO !i 876 ! 845 877 846 878 endif … … 850 882 z0_new = SQRT(z0_new**2+rugoro**2) 851 883 alblw(1:knon) = alb_new(1:knon) 884 852 885 853 886 else if (nisurf == is_lic) then … … 2065 2098 ! la glace de mer pour un "slab" ocean de 50m 2066 2099 ! 2067 ! I. Musat 04.02.2005 2100 ! Conception: Laurent Li 2101 ! Re-ecriture + adaptation LMDZ4: I. Musat 2068 2102 ! 2069 2103 ! input: … … 2100 2134 ! 2101 2135 ! Variables locales : 2136 REAL :: amn, amx 2102 2137 INTEGER, save :: lmt_pas, julien, idayvrai 2103 2138 REAL, parameter :: unjour=86400. … … 2149 2184 ! 2150 2185 ENDIF !debut 2186 ! 2187 IF (check ) THEN 2188 amn=MIN(tmp_tslab(1),1000.) 2189 amx=MAX(tmp_tslab(1),-1000.) 2190 DO i=2, klon 2191 amn=MIN(tmp_tslab(i),amn) 2192 amx=MAX(tmp_tslab(i),amx) 2193 ENDDO 2194 ! 2195 PRINT*,' debut min max tslab',amn,amx 2196 ! 2197 !! 2198 PRINT*,' itap,lmt_pas unjour',itap,lmt_pas,unjour 2199 ENDIF 2200 !! 2201 ! 2151 2202 pctsrf_slab(1:klon,1:nbsrf) = pctsrf(1:klon,1:nbsrf) 2152 2203 ! … … 2198 2249 ! et pctsrf(i,is_sic) croit lineairement avec seaice de 0. a 20cm d'epaisseur 2199 2250 ! 2251 2252 IF(.NOT.ok_slab_sicOBS) then 2200 2253 pctsrf_slab(i,is_sic)=MIN(siceh(i)/0.20, & 2201 2254 & 1.-(pctsrf_slab(i,is_ter)+pctsrf_slab(i,is_lic))) 2202 2255 pctsrf_slab(i,is_oce)=1.0 - & 2203 2256 & (pctsrf_slab(i,is_ter)+pctsrf_slab(i,is_lic)+pctsrf_slab(i,is_sic)) 2257 ELSE 2258 IF (i.EQ.1) print*,'cas ok_slab_sicOBS TRUE : passe sur la modif.' 2259 ENDIF !(.NOT.ok_slab_sicOBS) then 2204 2260 ENDIF !pctsrf 2205 2261 ENDDO … … 2220 2276 ! 2221 2277 IF (MOD(itap,lmt_pas).EQ.0) THEN !fin de journee 2278 ! 2279 ! calcul tslab 2280 amn=MIN(tmp_tslab(1),1000.) 2281 amx=MAX(tmp_tslab(1),-1000.) 2222 2282 DO i = 1, klon 2223 2283 IF ((pctsrf_slab(i,is_oce).GT.epsfra).OR. & … … 2229 2289 slab_bils(i) = 0. 2230 2290 ENDIF !pctsrf 2291 ! 2292 IF (check) THEN 2293 IF(i.EQ.1) THEN 2294 PRINT*,'i tmp_tslab MOD(itap,lmt_pas).EQ.0 sicINTER',i,itap, & 2295 & tmp_tslab(i), tmp_seaice(i) 2296 ENDIF 2297 ! 2298 amn=MIN(tmp_tslab(i),amn) 2299 amx=MAX(tmp_tslab(i),amx) 2300 ENDIF 2231 2301 ENDDO !klon 2232 2302 ENDIF !(MOD(itap,lmt_pas).EQ.0) THEN 2303 ! 2304 IF ( check ) THEN 2305 PRINT*,'fin min max tslab',amn,amx 2306 ENDIF 2233 2307 ! 2234 2308 tslab = tmp_tslab
Note: See TracChangeset
for help on using the changeset viewer.