Ignore:
Timestamp:
Dec 10, 2009, 10:02:56 AM (15 years ago)
Author:
Laurent Fairhead
Message:

Merged LMDZ4-dev branch changes r1241:1278 into the trunk
Running trunk and LMDZ4-dev in LMDZOR configuration on local
machine (sequential) and SX8 (4-proc) yields identical results
(restart and restartphy are identical binarily)
Log history from r1241 to r1278 is available by switching to
source:LMDZ4/branches/LMDZ4-dev-20091210

Location:
LMDZ4/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk

  • LMDZ4/trunk/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r1146 r1279  
    6868!   spechum      humidite specifique 1ere couche
    6969!   epot_air     temp pot de l'air
    70 !   ccanopy      concentration CO2 canopee
     70!   ccanopy      concentration CO2 canopee, correspond au co2_send de
     71!                carbon_cycle_mod ou valeur constant co2_ppm
    7172!   tq_cdrag     cdrag
    7273!   petAcoef     coeff. A de la resolution de la CL pour t
     
    9596!   qsurf        air moisture at surface
    9697!
     98    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_land_inst, fco2_lu_inst
     99    IMPLICIT NONE
     100
    97101    INCLUDE "indicesol.h"
    98102    INCLUDE "temps.h"
     
    135139    INTEGER                                   :: error
    136140    REAL, DIMENSION(klon)                     :: swdown_vrai
     141    REAL, DIMENSION(klon)                     :: fco2_land_comp  ! sur grille compresse
     142    REAL, DIMENSION(klon)                     :: fco2_lu_comp    ! sur grille compresse
    137143    CHARACTER (len = 20)                      :: modname = 'surf_land_orchidee'
    138144    CHARACTER (len = 80)                      :: abort_message
     
    334340       ENDIF
    335341
     342!
     343! Allocate variables needed for carbon_cycle_mod
     344!
     345       IF (carbon_cycle_cpl) THEN
     346          IF (.NOT. ALLOCATED(fco2_land_inst)) THEN
     347             ALLOCATE(fco2_land_inst(klon),stat=error)
     348             IF (error /= 0)  CALL abort_gcm(modname,'Pb in allocation fco2_land_inst',1)
     349             
     350             ALLOCATE(fco2_lu_inst(klon),stat=error)
     351             IF(error /=0) CALL abort_gcm(modname,'Pb in allocation fco2_lu_inst',1)
     352          END IF
     353       END IF
     354
    336355    ENDIF                          ! (fin debut)
    337356
     
    378397
    379398#ifndef CPP_MPI
    380 #define ORC_PREPAR
    381 #endif
    382 
    383 #ifdef ORC_PREPAR
    384399          ! Interface for ORCHIDEE compiled in sequential mode(without preprocessing flag CPP_MPI)
    385400          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
     
    394409
    395410#else         
    396           ! Interface for ORCHIDEE version 1.9 or later compiled in parallel mode(with preprocessing flag CPP_MPI)
     411          ! Interface for ORCHIDEE version 1.9 or later(1.9.2, 1.9.3, 1.9.4) compiled in parallel mode(with preprocessing flag CPP_MPI)
    397412          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, offset, knon, ktindex, &
    398413               orch_comm, dtime, lrestart_read, lrestart_write, lalo, &
     
    417432    IF (knon /=0) THEN
    418433   
    419 #ifdef ORC_PREPAR
     434#ifndef CPP_MPI
    420435       ! Interface for ORCHIDEE compiled in sequential mode(without preprocessing flag CPP_MPI)
    421436       CALL intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime, &
     
    463478
    464479    IF (debut) lrestart_read = .FALSE.
     480
     481
     482! JG : TEMPORAIRE!!!! Les variables fco2_land_comp et fco2_lu_comp seront plus tard en sortie d'ORCHIDEE
     483!      ici mis a valeur quelquonque pour test. Ces variables sont sur la grille compresse avec uniquement des points de terres
     484
     485    fco2_land_comp(:) = 1.
     486    fco2_lu_comp(:)   = 10.
     487
     488! Decompress variables for the module carbon_cycle_mod
     489    IF (carbon_cycle_cpl) THEN
     490       fco2_land_inst(:)=0.
     491       fco2_lu_inst(:)=0.
     492       
     493       DO igrid = 1, knon
     494          ireal = knindex(igrid)
     495          fco2_land_inst(ireal) = fco2_land_comp(igrid)
     496          fco2_lu_inst(ireal)   = fco2_lu_comp(igrid)
     497       END DO
     498    END IF
     499
    465500#endif   
    466501  END SUBROUTINE surf_land_orchidee
     
    628663          displs(i)=displs(i-1)+knon_nb(i-1)
    629664       ENDDO
    630     ENDIF
     665   ELSE
     666       ALLOCATE(neighbours_g(1,8))
     667   ENDIF
    631668   
    632669    ktindex_p(1:knon)=ktindex(1:knon)+klon_mpi_begin-1+iim-1
Note: See TracChangeset for help on using the changeset viewer.