Changeset 837 for LMDZ4/trunk/libf


Ignore:
Timestamp:
Aug 30, 2007, 10:58:33 AM (17 years ago)
Author:
lsce
Message:

AC + ACo + JG : voir meme commit sur phylmd

Location:
LMDZ4/trunk/libf/phytherm
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phytherm/cpl_mod.F90

    r814 r837  
    1717! Use statements
    1818!*************************************************************************************
    19   USE dimphy, ONLY : klon, zmasq
     19  USE dimphy, ONLY : klon
    2020  USE mod_phys_lmdz_para
    2121  USE ioipsl
     
    7171  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: pctsrf_sav   
    7272  !$OMP THREADPRIVATE(pctsrf_sav)
    73   REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: zmasq2D
    74   !$OMP THREADPRIVATE(zmasq2D)
    7573  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: unity
    7674  !$OMP THREADPRIVATE(unity)
     
    181179    ALLOCATE(read_alb_sic(iim, jj_nb), stat = error)
    182180    sum_error = sum_error + error
    183     ALLOCATE(zmasq2D(iim, jj_nb), stat = error)
    184     sum_error = sum_error + error   
    185    
    186181
    187182    IF (sum_error /= 0) THEN
     
    202197    cpl_taux = 0.   ; cpl_tauy = 0.  ; cpl_rriv2D = 0. ; cpl_rcoa2D = 0.
    203198    cpl_rlic2D = 0. ; cpl_windsp = 0.
    204 
    205 !*************************************************************************************
    206 ! Transform the land-ocean mask into 2D grid.
    207 ! Colorize zmasq2D with 99 so that after gath2cpl points not valid can be recognized.
    208 !
    209 !*************************************************************************************
    210     zmasq2D(:,:) = 99.
    211     CALL gath2cpl(zmasq, zmasq2D, klon, unity)
    212199
    213200!*************************************************************************************
     
    936923    INTEGER, DIMENSION(iim*(jjm+1))                      :: ndexct
    937924    REAL                                                 :: Up, Down
    938     REAL, DIMENSION(iim, jj_nb)                       :: tmp_lon, tmp_lat
    939     REAL, DIMENSION(iim, jj_nb, 4)                    :: pctsrf2D
    940     REAL, DIMENSION(iim, jj_nb)                       :: deno
     925    REAL, DIMENSION(iim, jj_nb)                          :: tmp_lon, tmp_lat
     926    REAL, DIMENSION(iim, jj_nb, 4)                       :: pctsrf2D
     927    REAL, DIMENSION(iim, jj_nb)                          :: deno
    941928    CHARACTER(len = 20)                                  :: modname = 'cpl_send_all'
    942929    CHARACTER(len = 80)                                  :: abort_message
    943930   
    944931! Variables with fields to coupler
    945     REAL, DIMENSION(iim, jj_nb)                       :: tmp_taux
    946     REAL, DIMENSION(iim, jj_nb)                       :: tmp_tauy
    947     REAL, DIMENSION(iim, jj_nb)                       :: tmp_calv
     932    REAL, DIMENSION(iim, jj_nb)                          :: tmp_taux
     933    REAL, DIMENSION(iim, jj_nb)                          :: tmp_tauy
     934    REAL, DIMENSION(iim, jj_nb)                          :: tmp_calv
    948935! Table with all fields to send to coupler
    949     REAL, DIMENSION(iim, jj_nb, jpflda2o1+jpflda2o2)  :: tab_flds
     936    REAL, DIMENSION(iim, jj_nb, jpflda2o1+jpflda2o2)     :: tab_flds
    950937#ifdef CPP_PARA
    951938    INCLUDE 'mpif.h'
     
    10361023    tmp_tauy(:,:)    = 0.0
    10371024   
    1038     ! For all valid grid cells not entier land
    1039     WHERE (zmasq2D /= 1. .AND. zmasq2D /=99. )
    1040        deno =  pctsrf2D(:,:,is_oce) + pctsrf2D(:,:,is_sic) ! fraction oce+seaice
     1025
     1026    ! fraction oce+seaice
     1027    deno =  pctsrf2D(:,:,is_oce) + pctsrf2D(:,:,is_sic)
     1028    ! For all valid grid cells containing some fraction of ocean or sea-ice
     1029    WHERE ( deno(:,:) /= 0 )
     1030       tab_flds(:,:,15) = cpl_rain2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1031            cpl_rain2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
     1032       tab_flds(:,:,16) = cpl_snow2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1033            cpl_snow2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
    10411034       
    1042        tab_flds(:,:,15) = cpl_rain2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1043             cpl_rain2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
    1044        tab_flds(:,:,16) = cpl_snow2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1045             cpl_snow2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
    1046        
    1047        tmp_taux = cpl_taux2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1048             cpl_taux2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
    1049        tmp_tauy = cpl_tauy2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno +    &
    1050             cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno
     1035       tmp_taux = cpl_taux2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1036            cpl_taux2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
     1037       tmp_tauy = cpl_tauy2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
     1038            cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
    10511039    ENDWHERE
    10521040
  • LMDZ4/trunk/libf/phytherm/surf_land_orchidee_mod.F90

    r815 r837  
    371371#endif
    372372#ifdef ORC_PREPAR
    373           ! Interface for version 1.8 or earlier of ORCHIDEE
     373          ! Interface for ORCHIDEE version 1.9 or earlier compiled in sequential mode(without preprocessing flag CPP_PARA)
    374374          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
    375375               lrestart_read, lrestart_write, lalo, &
     
    383383
    384384#else         
     385          ! Interface for ORCHIDEE version 1.9 compiled in parallel mode(with preprocessing flag CPP_PARA)
    385386          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, offset, knon, ktindex, &
    386387               orch_comm, dtime, lrestart_read, lrestart_write, lalo, &
     
    406407   
    407408#ifdef ORC_PREPAR
    408        ! Interface for version 1.8 or earlier of ORCHIDEE
    409        CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
     409       ! Interface for ORCHIDEE version 1.9 or earlier compiled in sequential mode(without preprocessing flag CPP_PARA)
     410       CALL intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime, &
    410411            lrestart_read, lrestart_write, lalo, &
    411412            contfrac, neighbours, resolution, date0, &
    412413            zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
    413414            cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
    414             precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
     415            precip_rain, precip_snow, lwdown, swnet, swdown_vrai, ps, &
    415416            evap, fluxsens, fluxlat, coastalflow, riverflow, &
    416417            tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
     
    418419       
    419420#else
    420 
     421       ! Interface for ORCHIDEE version 1.9 compiled in parallel mode(with preprocessing flag CPP_PARA)
    421422       CALL intersurf_main (itime+itau_phy, iim, jjm+1,offset, knon, ktindex, &
    422423            orch_comm,dtime, lrestart_read, lrestart_write, lalo, &
Note: See TracChangeset for help on using the changeset viewer.