Changeset 815 for LMDZ4/trunk/libf
- Timestamp:
- Jul 14, 2007, 10:31:47 PM (17 years ago)
- Location:
- LMDZ4/trunk/libf/phytherm
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ4/trunk/libf/phytherm/iniphysiq.F
r814 r815 13 13 USE mod_phys_lmdz_para 14 14 USE comgeomphy 15 15 16 IMPLICIT NONE 16 17 c … … 57 58 REAL pcu(klon_glo),pcv(klon_glo) 58 59 INTEGER pdayref 59 INTEGER :: ibegin,iend 60 INTEGER :: ibegin,iend,offset 60 61 61 62 REAL ptimestep … … 78 79 c$OMP PARALLEL PRIVATE(ibegin,iend) 79 80 c$OMP+ SHARED(parea,pcu,pcv,plon,plat) 80 81 airephy(1:klon_omp)=parea(klon_omp_begin:klon_omp_end) 82 cuphy(1:klon_omp)=pcu(klon_omp_begin:klon_omp_end) 83 cvphy(1:klon_omp)=pcv(klon_omp_begin:klon_omp_end) 84 rlond(1:klon_omp) = plon(klon_omp_begin:klon_omp_end) 85 rlatd(1:klon_omp) = plat(klon_omp_begin:klon_omp_end) 81 82 offset=klon_mpi_begin-1 83 airephy(1:klon_omp)=parea(offset+klon_omp_begin: 84 & offset+klon_omp_end) 85 cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end) 86 cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end) 87 rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end) 88 rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end) 86 89 87 90 call suphec … … 92 95 print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...' 93 96 94 95 97 RETURN 96 98 9999 STOP'Cette version demande les fichier rnatur.dat et surf.def' -
LMDZ4/trunk/libf/phytherm/ocean_cpl_mod.F90
r814 r815 12 12 USE calcul_fluxs_mod, ONLY : calcul_fluxs 13 13 USE climb_wind_mod, ONLY : calcul_wind_flux 14 USE mod_clvent, ONLY : calcul_flux_vent15 USE surface_data, ONLY : newwind16 14 17 15 IMPLICIT NONE … … 160 158 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l) 161 159 162 !jg : temporary test, only calcul_flux_wind should be saved in the future163 160 ! Calcultate the flux of u and v at surface 164 IF (newwind) THEN 165 ! calculate flux with new methode 166 CALL calcul_wind_flux(knon, dtime, taux, tauy) 167 ELSE 168 ! use results from old clvent. jg: TO BE REMOVED 169 CALL calcul_flux_vent(klon, taux, tauy) 170 ENDIF 171 161 CALL calcul_wind_flux(knon, dtime, taux, tauy) 162 172 163 173 164 !**************************************************************************************** … … 312 303 313 304 ! Calcultate the flux of u and v at surface 314 IF (newwind) THEN 315 ! calculate flux with new methode 316 CALL calcul_wind_flux(knon, dtime, taux, tauy) 317 ELSE 318 ! use results from old clvent. jg: TO BE REMOVED 319 CALL calcul_flux_vent(klon, taux, tauy) 320 END IF 321 305 CALL calcul_wind_flux(knon, dtime, taux, tauy) 306 322 307 !**************************************************************************************** 323 308 ! Flux ocean-atmosphere useful for "slab" ocean but here calculated only for printing -
LMDZ4/trunk/libf/phytherm/pbl_surface_mod.F90
r814 r815 13 13 USE mod_phys_lmdz_para, ONLY : mpi_size 14 14 USE ioipsl 15 USE surface_data, ONLY : ocean, ok_veget , debug_surf, newwind15 USE surface_data, ONLY : ocean, ok_veget 16 16 USE surf_land_mod, ONLY : surf_land 17 17 USE surf_landice_mod, ONLY : surf_landice … … 22 22 USE climb_wind_mod, ONLY : climb_wind_down, climb_wind_up 23 23 USE coef_diff_turb_mod, ONLY : coef_diff_turb 24 25 !jg+ temporary26 USE mod_clvent, ONLY : clvent, save_flux27 !jg-28 24 29 25 IMPLICIT NONE … … 455 451 456 452 457 !jg+ temporary test458 REAL, DIMENSION(klon,klev) :: y_flux_u_old, y_flux_v_old459 REAL, DIMENSION(klon,klev) :: y_d_u_old, y_d_v_old460 !jg-461 462 453 !**************************************************************************************** 463 454 ! End of declarations … … 698 689 ycoefm, ycoefh) 699 690 700 !jg+701 !****************************************************************************************702 ! => Old method703 ! Calculer la diffusion des vitesses "u" et "v"704 ! Output can be used : y_d_u_old, y_flux_u_old, y_d_v_old, y_flux_v_old705 !706 !****************************************************************************************707 CALL clvent(knon,dtime,yu1,yv1,ycoefm,yt,yu,ypaprs,ypplay,ydelp, &708 y_d_u_old, y_flux_u_old)709 CALL clvent(knon,dtime,yu1,yv1,ycoefm,yt,yv,ypaprs,ypplay,ydelp, &710 y_d_v_old, y_flux_v_old)711 ! save_flux est utile pour pouvoir utilise calcul_flux_vent plus tard712 CALL save_flux(klon, y_flux_u_old(:,1), y_flux_v_old(:,1))713 !jg-714 715 691 !**************************************************************************************** 716 692 ! … … 848 824 y_flux_u, y_flux_v, y_d_u, y_d_v) 849 825 850 !jg+ temporary for testing851 ! Use the results from old method852 IF (.NOT. newwind) THEN853 y_flux_u(:,:) = y_flux_u_old(:,:)854 y_flux_v(:,:) = y_flux_v_old(:,:)855 y_d_u(:,:) = y_d_u_old(:,:)856 y_d_v(:,:) = y_d_v_old(:,:)857 ENDIF858 !jg-859 860 826 DO j = 1, knon 861 827 y_dflux_t(j) = y_dflux_t(j) * ypct(j) -
LMDZ4/trunk/libf/phytherm/readsulfate.F
r814 r815 192 192 ig=ig+1 193 193 if (ig.gt.klon) write (*,*) 'shit' 194 so4(ig,k,it) = so4_1(i,jjm+1 -j,klev+1-k,it)194 so4(ig,k,it) = so4_1(i,jjm+1+1-j,klev+1-k,it) 195 195 ENDDO 196 196 ENDDO … … 430 430 ig=ig+1 431 431 if (ig.gt.klon) write (*,*) 'shit' 432 pi_so4(ig,k,it) = pi_so4_1(i,jjm+1 -j,klev+1-k,it)432 pi_so4(ig,k,it) = pi_so4_1(i,jjm+1+1-j,klev+1-k,it) 433 433 ENDDO 434 434 ENDDO … … 599 599 600 600 #ifdef NC_DOUBLE 601 status = NF_GET_VAR _DOUBLE(NCID, VARID, START, COUNT, so4mth)601 status = NF_GET_VARA_DOUBLE(NCID, VARID, START, COUNT, so4mth) 602 602 #else 603 status = NF_GET_VAR _REAL(NCID, VARID, START, COUNT, so4mth)603 status = NF_GET_VARA_REAL(NCID, VARID, START, COUNT, so4mth) 604 604 #endif 605 605 IF (STATUS .NE. NF_NOERR) write (*,*) 'err in read data',status -
LMDZ4/trunk/libf/phytherm/surf_land_orchidee_mod.F90
r814 r815 366 366 IF (knon /=0) THEN 367 367 CALL Init_orchidee_index(knon,orch_comm,knindex,offset,ktindex) 368 369 #ifndef CPP_PARA 368 370 #define ORC_PREPAR 371 #endif 369 372 #ifdef ORC_PREPAR 370 call intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, & 371 & lrestart_read, lrestart_write, lalo, & 372 & contfrac, neighbours, resolution, date0, & 373 & zlev, u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, & 374 & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, & 375 & precip_rain, precip_snow, lwdown, swnet, swdown, ps, & 376 & evap, fluxsens, fluxlat, coastalflow, riverflow, & 377 & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, & 378 & lon_scat, lat_scat) 373 ! Interface for version 1.8 or earlier of ORCHIDEE 374 CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, & 375 lrestart_read, lrestart_write, lalo, & 376 contfrac, neighbours, resolution, date0, & 377 zlev, u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, & 378 cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, & 379 precip_rain, precip_snow, lwdown, swnet, swdown, ps, & 380 evap, fluxsens, fluxlat, coastalflow, riverflow, & 381 tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, & 382 lon_scat, lat_scat) 379 383 380 384 #else … … 402 406 403 407 #ifdef ORC_PREPAR 404 call intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, & 405 & lrestart_read, lrestart_write, lalo, & 406 & contfrac, neighbours, resolution, date0, & 407 & zlev, u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, & 408 & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, & 409 & precip_rain, precip_snow, lwdown, swnet, swdown, ps, & 410 & evap, fluxsens, fluxlat, coastalflow, riverflow, & 411 & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, & 412 & lon_scat, lat_scat) 413 408 ! Interface for version 1.8 or earlier of ORCHIDEE 409 CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, & 410 lrestart_read, lrestart_write, lalo, & 411 contfrac, neighbours, resolution, date0, & 412 zlev, u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, & 413 cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, & 414 precip_rain, precip_snow, lwdown, swnet, swdown, ps, & 415 evap, fluxsens, fluxlat, coastalflow, riverflow, & 416 tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, & 417 lon_scat, lat_scat) 418 414 419 #else 415 420 … … 482 487 INTEGER :: mpi_size 483 488 INTEGER :: ierr 484 489 ! 490 ! End definition 491 !**************************************************************************************** 492 485 493 MyLastPoint=klon_mpi_begin-1+knindex(knon)+iim-1 486 494 … … 534 542 INTEGER :: color 535 543 INTEGER :: ierr 536 544 ! 545 ! End definition 546 !**************************************************************************************** 547 537 548 IF (knon==0) THEN 538 549 color = 0 … … 557 568 #endif 558 569 559 570 ! Input arguments 571 !**************************************************************************************** 560 572 INTEGER, INTENT(IN) :: knon 561 INTEGER, DIMENSION(knon,8), INTENT(OUT) :: neighbours562 573 INTEGER, DIMENSION(klon), INTENT(IN) :: ktindex 563 574 REAL, DIMENSION(klon), INTENT(IN) :: pctsrf 564 575 565 INTEGER :: knon_nb(0:mpi_size-1) 566 INTEGER,DIMENSION(0:mpi_size-1) :: displs 567 INTEGER,ALLOCATABLE :: ktindex_g(:) 568 REAL :: pctsrf_g(klon_glo) 569 INTEGER,ALLOCATABLE ::neighbours_g(:,:) 570 INTEGER :: knon_g 571 REAL*8 :: correspond(iim,jjm+1) 572 INTEGER :: i,igrid,jj,ij,iglob,ierr,ireal,index 573 INTEGER, DIMENSION(8,3) :: off_ini 574 INTEGER, DIMENSION(8) :: offset 575 INTEGER :: ktindex_p(knon) 576 576 ! Output arguments 577 !**************************************************************************************** 578 INTEGER, DIMENSION(knon,8), INTENT(OUT) :: neighbours 579 580 ! Local variables 581 !**************************************************************************************** 582 INTEGER :: knon_g 583 INTEGER :: i, igrid, jj, ij, iglob 584 INTEGER :: ierr, ireal, index 585 INTEGER, DIMENSION(0:mpi_size-1) :: knon_nb 586 INTEGER, DIMENSION(0:mpi_size-1) :: displs 587 INTEGER, DIMENSION(8,3) :: off_ini 588 INTEGER, DIMENSION(8) :: offset 589 INTEGER, DIMENSION(knon) :: ktindex_p 590 INTEGER, DIMENSION(iim,jjm+1) :: correspond 591 INTEGER, ALLOCATABLE, DIMENSION(:) :: ktindex_g 592 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: neighbours_g 593 REAL, DIMENSION(klon_glo) :: pctsrf_g 594 595 ! 596 ! End definition 597 !**************************************************************************************** 598 577 599 IF (is_sequential) THEN 578 600 knon_nb(:)=knon -
LMDZ4/trunk/libf/phytherm/surface_data.F90
r814 r815 10 10 REAL, PARAMETER :: calsno=1./(2.3867e+06*.15) 11 11 12 LOGICAL, SAVE :: debug_surf=.FALSE.13 !$OMP THREADPRIVATE(debug_surf)14 LOGICAL, SAVE :: newwind=.FALSE.15 !$OMP THREADPRIVATE(newwind)16 17 12 LOGICAL, SAVE :: ok_veget ! true for use of vegetation model ORCHIDEE 18 13 !$OMP THREADPRIVATE(ok_veget)
Note: See TracChangeset
for help on using the changeset viewer.