Changeset 1227


Ignore:
Timestamp:
Aug 10, 2009, 1:45:04 PM (15 years ago)
Author:
jghattas
Message:
  • Inclusion d'un premier version du cycle de carbon dans LMDZ. Attention

!! Il s'agit d'un version ou les nouveaux cles cycle_carbon_tr et
cycle_carbon_cpl ne sont pas teste. Avec les ancinenes parametres le
modele donne les memes resultats qu'avant. L'interface avec ORCHIDEE n'a
pas encore etait modifie.

  • physiq.F, phys_cal_mod.F90 : ajout d'un nouveau module qui contient qq parametres pour le calendrier et le pas de temps acutelle de la physiq. Ce module pourrait etre elargie plus tard / LF + JG


  • infotrac.F90 : les noms du traceurs peut prendre un nom plus long (15 caracteres) dans traceur.def
Location:
LMDZ4/branches/LMDZ4-dev/libf
Files:
3 added
17 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/etat0_netcdf.F

    r1220 r1227  
    177177     &                 iflag_thermals_ed,iflag_thermals_optflux,        &
    178178     &                 iflag_coupl,iflag_clos,iflag_wake, read_climoz )
     179
     180
     181! co2_ppm0 : initial value of atmospheric CO2 from .def file (co2_ppm value)
     182      co2_ppm0 = co2_ppm
    179183
    180184      dtvr   = daysec/FLOAT(day_step)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3d/infotrac.F90

    r1191 r1227  
    5656    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
    5757
    58     CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     58    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    5959    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tracnam ! name from INCA
    6060    CHARACTER(len=3), DIMENSION(30) :: descrq
     
    329329    DEALLOCATE(tracnam)
    330330
    331 999 FORMAT (i2,1x,i2,1x,a8)
     331999 FORMAT (i2,1x,i2,1x,a15)
    332332
    333333  END SUBROUTINE infotrac_init
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/etat0_netcdf.F

    r1220 r1227  
    177177     &                 iflag_thermals_ed,iflag_thermals_optflux,        &
    178178     &                 iflag_coupl,iflag_clos,iflag_wake, read_climoz )
     179
     180! co2_ppm0 : initial value of atmospheric CO2 from .def file (co2_ppm value)
     181      co2_ppm0 = co2_ppm
    179182
    180183      dtvr   = daysec/FLOAT(day_step)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/infotrac.F90

    r1191 r1227  
    5656    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
    5757
    58     CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     58    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
    5959    CHARACTER(len=8), ALLOCATABLE, DIMENSION(:) :: tracnam ! name from INCA
    6060    CHARACTER(len=3), DIMENSION(30) :: descrq
     
    329329    DEALLOCATE(tracnam)
    330330
    331 999 FORMAT (i2,1x,i2,1x,a8)
     331999 FORMAT (i2,1x,i2,1x,a15)
    332332
    333333  END SUBROUTINE infotrac_init
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/clesphys.h

    r1204 r1227  
    1212       LOGICAL ok_limitvrai
    1313       INTEGER nbapp_rad, iflag_con
    14        REAL co2_ppm, solaire
     14       REAL co2_ppm, co2_ppm0, solaire
    1515       REAL(kind=8) RCO2, RCH4, RN2O, RCFC11, RCFC12 
    1616       REAL(kind=8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt
     
    7171     &     , freq_ISCCP, ecrit_ISCCP, ip_ebil_phy                       &
    7272     &     , ok_lic_melt, cvl_corr, aer_type                            &
    73      &     , qsol0, iflag_rrtm, ok_strato,ok_hines,ecrit_LES
     73     &     , qsol0, iflag_rrtm, ok_strato,ok_hines,ecrit_LES            &
     74     &     , co2_ppm0
    7475     
    7576!$OMP THREADPRIVATE(/clesphys/)
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/conf_phys.F90

    r1225 r1227  
    2121   use IOIPSL
    2222   USE surface_data
     23   USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl
    2324
    2425   implicit none
     
    144145  LOGICAL,SAVE :: ok_strato_omp
    145146  LOGICAL,SAVE :: ok_hines_omp
     147  LOGICAL      :: read_climoz_omp
     148  LOGICAL      :: carbon_cycle_tr_omp
     149  LOGICAL      :: carbon_cycle_cpl_omp
    146150
    147151  logical, intent(out):: read_climoz ! read ozone climatology, OpenMP shared
     
    12621266  call getin('ecrit_LES', ecrit_LES_omp)
    12631267!
    1264   read_climoz = .false. ! default value
    1265   call getin('read_climoz', read_climoz)
     1268  read_climoz_omp = .false. ! default value
     1269  call getin('read_climoz', read_climoz_omp)
     1270
     1271  carbon_cycle_tr_omp=.FALSE.
     1272  CALL getin('carbon_cycle_tr',carbon_cycle_tr_omp)
     1273
     1274  carbon_cycle_cpl_omp=.FALSE.
     1275  CALL getin('carbon_cycle_cpl',carbon_cycle_cpl_omp)
    12661276
    12671277!$OMP END MASTER
     
    13931403    ok_LES = ok_LES_omp
    13941404    ecrit_LES = ecrit_LES_omp
    1395    
     1405    read_climoz = read_climoz_omp
     1406    carbon_cycle_tr = carbon_cycle_tr_omp
     1407    carbon_cycle_cpl = carbon_cycle_cpl_omp
     1408
    13961409! Test of coherence between type_ocean and version_ocean
    13971410    IF (type_ocean=='couple' .AND. (version_ocean/='opa8' .AND. version_ocean/='nemo') ) THEN
     
    15241537  write(numout,*) 'ok_hines = ',  ok_hines
    15251538  write(numout,*) 'read_climoz = ', read_climoz
     1539  write(numout,*) 'carbon_cycle_tr = ', carbon_cycle_tr
     1540  write(numout,*) 'carbon_cycle_cpl = ', carbon_cycle_cpl
    15261541 
    15271542!$OMP END MASTER
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/cpl_mod.F90

    r1152 r1227  
    3939!*************************************************************************************
    4040! variable for coupling period
    41   INTEGER, SAVE                             :: nexca
     41  INTEGER, SAVE :: nexca
    4242  !$OMP THREADPRIVATE(nexca)
    4343
     
    9595!
    9696  SUBROUTINE cpl_init(dtime, rlon, rlat)
     97    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
    9798
    9899    INCLUDE "dimensions.h"
     
    183184    sum_error = sum_error + error
    184185
    185     IF (cpl_carbon_cycle) THEN
     186    IF (carbon_cycle_cpl) THEN
    186187       ALLOCATE(read_co2(iim, jj_nb), stat = error)
    187188       sum_error = sum_error + error
    188189       ALLOCATE(cpl_atm_co2(klon,2), stat = error)
     190       sum_error = sum_error + error
     191
     192! Allocate variable in carbon_cycle_mod
     193       ALLOCATE(fco2_ocn_day(klon), stat = error)
    189194       sum_error = sum_error + error
    190195    END IF
     
    275280    USE surface_data
    276281    USE phys_state_var_mod, ONLY : rlon, rlat
    277 
     282    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
     283   
    278284    INCLUDE "indicesol.h"
    279285    INCLUDE "temps.h"
     
    364370      ENDIF
    365371
    366        IF (cpl_carbon_cycle) THEN
     372       IF (carbon_cycle_cpl) THEN
    367373!$OMP MASTER
    368374           read_co2(:,:) = tab_read_flds(:,:,idr_oceco2) ! CO2 flux
     
    403409! The temperature is transformed into 1D array with valid points from index 1 to knon.
    404410!
     411    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
    405412    INCLUDE "indicesol.h"
    406413
     
    418425! Local variables
    419426!*************************************************************************************
    420     INTEGER               :: i
    421     REAL, DIMENSION(klon) :: sic_new
     427    INTEGER                  :: i
     428    INTEGER, DIMENSION(klon) :: index
     429    REAL, DIMENSION(klon)    :: sic_new
    422430
    423431!*************************************************************************************
     
    430438    CALL cpl2gath(read_v0, v0_new, knon, knindex)
    431439
    432     IF (cpl_carbon_cycle) THEN
    433        WRITE(*,*) 'cpl_carbon_cycle TO BE DONE!!'
    434        !!    var_co2 will be a intent(out) argument
    435        !!    CALL cpl2gath(read_co2, var_co2, knon, knindex)
     440!*************************************************************************************
     441! Transform read_co2 into uncompressed 1D variable fco2_ocn_day added directly in
     442! the module carbon_cycle_mod
     443!
     444!*************************************************************************************
     445    IF (carbon_cycle_cpl) THEN
     446       DO i=1,klon
     447          index(i)=i
     448       END DO
     449       CALL cpl2gath(read_co2, fco2_ocn_day, klon, index)
    436450    END IF
     451
    437452!*************************************************************************************
    438453! The fields received from the coupler have to be weighted with the fraction of ocean
     
    511526! (it is done in cpl_send_seaice_fields).
    512527!
     528    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
    513529    INCLUDE "indicesol.h"
    514530    INCLUDE "dimensions.h"
     
    531547    CHARACTER(len = 25)                     :: modname = 'cpl_send_ocean_fields'
    532548    CHARACTER(len = 80)                     :: abort_message
    533     REAL, DIMENSION(klon)                   :: atm_co2    ! JG: to be an INTENT(IN) if cpl_carbon_cycle
    534549
    535550!*************************************************************************************
     
    556571       cpl_tauy(1:knon,cpl_index) = 0.0
    557572       cpl_windsp(1:knon,cpl_index) = 0.0
    558        IF (cpl_carbon_cycle) cpl_atm_co2(1:knon,cpl_index) = 0.0
     573       IF (carbon_cycle_cpl) cpl_atm_co2(1:knon,cpl_index) = 0.0
    559574    ENDIF
    560575       
     
    587602            windsp(ig)      / FLOAT(nexca)
    588603
    589        IF (cpl_carbon_cycle) THEN
    590           atm_co2=286.
     604       IF (carbon_cycle_cpl) THEN
    591605          cpl_atm_co2(ig,cpl_index) = cpl_atm_co2(ig,cpl_index) + &
    592                atm_co2(ig)/ FLOAT(nexca)
     606               co2_send(knindex(ig))/ FLOAT(nexca)
    593607       END IF
    594608     ENDDO
     
    627641          sum_error = sum_error + error
    628642         
    629           IF (cpl_carbon_cycle) THEN
     643          IF (carbon_cycle_cpl) THEN
    630644             ALLOCATE(cpl_atm_co22D(iim,jj_nb), stat=error)
    631645             sum_error = sum_error + error
     
    675689            knon, knindex)
    676690
    677        IF (cpl_carbon_cycle) &
     691       IF (carbon_cycle_cpl) &
    678692            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
    679693   ENDIF
     
    695709! the coupler.
    696710!
     711    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    697712    INCLUDE "indicesol.h"
    698713    INCLUDE "dimensions.h"
     
    803818          sum_error = sum_error + error
    804819
    805           IF (cpl_carbon_cycle) THEN
     820          IF (carbon_cycle_cpl) THEN
    806821             ALLOCATE(cpl_atm_co22D(iim,jj_nb), stat=error)
    807822             sum_error = sum_error + error
     
    926941! will be done in cpl_send_seaice_fields.
    927942!
     943
    928944    INCLUDE "dimensions.h"
    929945
     
    979995!   
    980996    USE surface_data
     997    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
    981998! Some includes
    982999!*************************************************************************************
     
    10371054    IF (version_ocean=='nemo') THEN
    10381055       tab_flds(:,:,ids_liqrun) = cpl_rriv2D(:,:) + cpl_rcoa2D(:,:)
    1039        IF (cpl_carbon_cycle) tab_flds(:,:,ids_atmco2)=cpl_atm_co22D(:,:)
     1056       IF (carbon_cycle_cpl) tab_flds(:,:,ids_atmco2)=cpl_atm_co22D(:,:)
    10401057    ELSE IF (version_ocean=='opa8') THEN
    10411058       tab_flds(:,:,ids_shfoce) = cpl_sols2D(:,:,1)
     
    12321249    sum_error = sum_error + error
    12331250   
    1234     IF (cpl_carbon_cycle) THEN
     1251    IF (carbon_cycle_cpl) THEN
    12351252       DEALLOCATE(cpl_atm_co22D, stat=error )
    12361253       sum_error = sum_error + error
     
    12481265  SUBROUTINE cpl2gath(champ_in, champ_out, knon, knindex)
    12491266  USE mod_phys_lmdz_para
    1250 ! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
    1251 ! au coupleur.
     1267! Cette routine transforme un champs de la grille 2D recu du coupleur sur la grille
     1268! 'gathered' (la grille physiq comprime).
    12521269!
    12531270!
    12541271! input:         
    1255 !   champ_in     champ sur la grille gathere       
     1272!   champ_in     champ sur la grille 2D
    12561273!   knon         nombre de points dans le domaine a traiter
    12571274!   knindex      index des points de la surface a traiter
    12581275!
    12591276! output:
    1260 !   champ_out    champ sur la grille 2D
     1277!   champ_out    champ sur la grille 'gatherd'
    12611278!
    12621279    INCLUDE "dimensions.h"
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/oasis.F90

    r1152 r1227  
    7272 
    7373  LOGICAL :: cpl_current
    74   LOGICAL :: cpl_carbon_cycle
    7574
    7675#ifdef CPP_COUPLE
     
    8887    USE IOIPSL
    8988    USE surface_data, ONLY : version_ocean
     89    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
     90
    9091    INCLUDE "dimensions.h"
    9192    INCLUDE "iniprint.h"
     
    105106    CHARACTER (len = 80)               :: abort_message
    106107    LOGICAL                            :: cpl_current_omp
    107     LOGICAL                            :: cpl_carbon_cycle_omp
    108108
    109109!*    1. Initializations
     
    133133    cpl_current = cpl_current_omp
    134134    WRITE(lunout,*) 'Couple ocean currents, cpl_current = ',cpl_current
    135 
    136 !************************************************************************************
    137 ! Define if coupling carbon cycle or not
    138 !************************************************************************************
    139 !$OMP MASTER
    140     cpl_carbon_cycle_omp = .FALSE.
    141     CALL getin('cpl_carbon_cycle', cpl_carbon_cycle_omp)
    142 !$OMP END MASTER
    143 !$OMP BARRIER
    144     cpl_carbon_cycle=cpl_carbon_cycle_omp
    145     WRITE(lunout,*) 'Couple carbon cycle , cpl_carbon_cycle = ',cpl_carbon_cycle
    146135
    147136!************************************************************************************
     
    174163        infosend(ids_icevap)%action = .TRUE. ; infosend(ids_icevap)%name = 'COICEVAP'
    175164        infosend(ids_liqrun)%action = .TRUE. ; infosend(ids_liqrun)%name = 'COLIQRUN'
    176         IF (cpl_carbon_cycle) THEN
     165        IF (carbon_cycle_cpl) THEN
    177166            infosend(ids_atmco2)%action = .TRUE. ; infosend(ids_atmco2)%name = 'COATMCO2'
    178167        ENDIF
     
    204193   ENDIF
    205194
    206    IF (cpl_carbon_cycle ) THEN
     195   IF (carbon_cycle_cpl ) THEN
    207196       inforecv(idr_oceco2)%action = .TRUE. ; inforecv(idr_oceco2)%name = 'SICO2FLX'
    208197   ENDIF
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/pbl_surface_mod.F90

    r1144 r1227  
    242242! pblT-----output-R- T au nveau HCL
    243243!
     244    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
     245    IMPLICIT NONE
     246
    244247    INCLUDE "indicesol.h"
    245248    INCLUDE "dimsoil.h"
     
    762765       ypsref(:) = ypaprs(:,1) 
    763766
    764 ! - Constant CO2 is copied to global grid
    765        r_co2_ppm(:) = co2_ppm
    766 
     767! - CO2 field on 2D grid to be sent to ORCHIDEE
     768!   Transform to compressed field
     769       IF (carbon_cycle_cpl) THEN
     770          DO i=1,knon
     771             r_co2_ppm(i) = co2_send(ni(i))
     772          END DO
     773       ELSE
     774          r_co2_ppm(:) = co2_ppm     ! Constant field
     775       END IF
    767776
    768777!****************************************************************************************
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/phyetat0.F

    r1191 r1227  
    2121      USE infotrac
    2222      USE traclmdz_mod,    ONLY : traclmdz_from_restart
     23      USE carbon_cycle_mod,ONLY : carbon_cycle_tr, carbon_cycle_cpl
    2324
    2425      IMPLICIT none
     
    106107         tab_cntrl(1)=dtime
    107108         tab_cntrl(2)=radpas
    108          co2_ppm_etat0      = tab_cntrl(3)
     109
     110c co2_ppm : value from the previous time step
     111         IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
     112            co2_ppm = tab_cntrl(3)
     113            RCO2    = co2_ppm * 1.0e-06  * 44.011/28.97
     114c ELSE : keep value from .def
     115         END IF
     116
     117c co2_ppm0 : initial value of atmospheric CO2 (from create_etat0_limit.e .def)
     118         co2_ppm0   = tab_cntrl(16)
     119
    109120         solaire_etat0      = tab_cntrl(4)
    110121         tab_cntrl(5)=iflag_con
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/phyredem.F

    r1225 r1227  
    7676CC      tab_cntrl(1) = dtime
    7777      tab_cntrl(2) = radpas
     78c co2_ppm : current value of atmospheric CO2
    7879      tab_cntrl(3) = co2_ppm
    7980      tab_cntrl(4) = solaire
     
    9091      tab_cntrl(14) = annee_ref
    9192      tab_cntrl(15) = itau_phy
     93
     94c co2_ppm0 : initial value of atmospheric CO2
     95      tab_cntrl(16) = co2_ppm0
    9296c
    9397      CALL put_var("controle","Parametres de controle",tab_cntrl)
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/phys_state_var_mod.F90

    r1215 r1227  
    1111      INTEGER, PARAMETER :: napisccp=1
    1212      INTEGER, SAVE :: radpas
    13       REAL, SAVE :: dtime, co2_ppm_etat0, solaire_etat0
     13      REAL, SAVE :: dtime, solaire_etat0
    1414!$OMP THREADPRIVATE(radpas)
    15 !$OMP THREADPRIVATE(dtime, co2_ppm_etat0, solaire_etat0)
     15!$OMP THREADPRIVATE(dtime, solaire_etat0)
    1616
    1717      REAL, ALLOCATABLE, SAVE :: rlat(:), rlon(:), pctsrf(:,:)
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/physiq.F

    r1226 r1227  
    1616!JG     $     histwrite, ju2ymds, ymds2ju, ioget_year_len
    1717      USE comgeomphy
     18      USE phys_cal_mod
    1819      USE write_field_phy
    1920      USE dimphy
     
    529530      REAL clesphy0( longcles      )
    530531c
    531 c Variables quasi-arguments
    532 c
    533       REAL xjour
    534       SAVE xjour
    535 c$OMP THREADPRIVATE(xjour)
    536 c
    537 c
    538532c Variables propres a la physique
    539533      INTEGER itap
     
    705699c
    706700!
    707 ! Gestion calendrier
    708 !
    709       REAL :: jD_1jan, jH_1jan
    710       INTEGER :: year_cur, mth_cur, day_cur, days_elapsed
    711       REAL :: hour, day_since_equinox
     701      REAL :: day_since_equinox
    712702! Date de l'equinoxe de printemps
    713703      INTEGER, parameter :: mth_eq=3, day_eq=21
     
    12041194
    12051195c======================================================================
    1206 ! Gestion calendrier
     1196! Gestion calendrier : mise a jour du module phys_cal_mod
    12071197!
    1208       call ju2ymds(jD_cur+jH_cur, year_cur, mth_cur, day_cur, hour)
    1209       call ymds2ju(year_cur, 1, 1, 0., jD_1jan)
    1210       jH_1jan = jD_1jan - int (jD_1jan)
    1211       jD_1jan = int (jD_1jan)
    1212       xjour = jD_cur - jD_1jan
    1213       days_elapsed = jD_cur - jD_1jan
     1198      CALL phys_cal_update(jD_cur,jH_cur)
    12141199
    12151200c
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/phytrac.F90

    r1212 r1227  
    212212     SELECT CASE(type_trac)
    213213     CASE('lmdz')
    214         CALL traclmdz_init(pctsrf, ftsol, aerosol, lessivage)
     214        CALL traclmdz_init(pctsrf, ftsol, tr_seri, aerosol, lessivage)
    215215     CASE('inca')
    216216        source(:,:)=0.
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/surf_land_orchidee_mod.F90

    r1144 r1227  
    4040       tsol_rad, tsurf_new, alb1_new, alb2_new, &
    4141       emis_new, z0_new, qsurf)
    42    USE mod_surf_para
    43    USE mod_synchro_omp
     42
     43    USE mod_surf_para
     44    USE mod_synchro_omp
    4445   
     46USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_land_inst, fco2_lu_inst
     47
    4548!   
    4649! Cette routine sert d'interface entre le modele atmospherique et le
     
    6770!   spechum      humidite specifique 1ere couche
    6871!   epot_air     temp pot de l'air
    69 !   ccanopy      concentration CO2 canopee
     72!   ccanopy      concentration CO2 canopee, correspond au co2_send de
     73!                carbon_cycle_mod ou valeur constant co2_ppm
    7074!   tq_cdrag     cdrag
    7175!   petAcoef     coeff. A de la resolution de la CL pour t
     
    134138    INTEGER                                   :: error
    135139    REAL, DIMENSION(klon)                     :: swdown_vrai
     140    REAL, DIMENSION(klon)                     :: fco2_land_comp  ! sur grille compresse
     141    REAL, DIMENSION(klon)                     :: fco2_lu_comp    ! sur grille compresse
    136142    CHARACTER (len = 20)                      :: modname = 'surf_land_orchidee'
    137143    CHARACTER (len = 80)                      :: abort_message
     
    341347          CALL abort_gcm(modname,abort_message,1)
    342348       ENDIF
    343 
     349!
     350! Allocate variables needed for carbon_cycle_mod
     351!
     352       IF (carbon_cycle_cpl) THEN
     353          IF (.NOT. ALLOCATED(fco2_land_inst)) THEN
     354             ALLOCATE(fco2_land_inst(klon),stat=error)
     355             IF (error /= 0)  CALL abort_gcm(modname,'Pb in allocation fco2_land_inst',1)
     356             
     357             ALLOCATE(fco2_lu_inst(klon),stat=error)
     358             IF(error /=0) CALL abort_gcm(modname,'Pb in allocation fco2_lu_inst',1)
     359          END IF
     360       END IF
     361       
    344362    ENDIF                          ! (fin debut)
     363 
    345364
    346365!
     
    443462   
    444463    IF (debut) CALL Finalize_surf_para
    445    
     464
     465   
     466! JG : TEMPORAIRE!!!! Les variables fco2_land_comp et fco2_lu_comp seront plus tard en sortie d'ORCHIDEE
     467!      ici mis a valeur quelquonque pour test. Ces variables sont sur la grille compresse avec uniquement des points de terres
     468
     469    fco2_land_comp(:) = 1.
     470    fco2_lu_comp(:)   = 10.
     471
     472! Decompress variables for the module carbon_cycle_mod
     473    IF (carbon_cycle_cpl) THEN
     474       fco2_land_inst(:)=0.
     475       fco2_lu_inst(:)=0.
     476       
     477       DO igrid = 1, knon
     478          ireal = knindex(igrid)
     479          fco2_land_inst(ireal) = fco2_land_comp(igrid)
     480          fco2_lu_inst(ireal)   = fco2_lu_comp(igrid)
     481       END DO
     482    END IF
     483
    446484  END SUBROUTINE surf_land_orchidee
    447485!
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r1144 r1227  
    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
  • LMDZ4/branches/LMDZ4-dev/libf/phylmd/traclmdz_mod.F90

    r1212 r1227  
    6565
    6666
    67   SUBROUTINE traclmdz_init(pctsrf, ftsol, aerosol, lessivage)
     67  SUBROUTINE traclmdz_init(pctsrf, ftsol, tr_seri, aerosol, lessivage)
    6868    ! This subroutine allocates and initialize module variables and control variables.
    6969    USE dimphy
    7070    USE infotrac
     71    USE carbon_cycle_mod, ONLY : carbon_cycle_init, carbon_cycle_tr, carbon_cycle_cpl
    7172
    7273    IMPLICIT NONE
     
    7576
    7677! Input variables
    77     REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: pctsrf ! Pourcentage de sol f(nature du sol)
    78     REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: ftsol  ! Temperature du sol (surf)(Kelvin)
    79    
     78    REAL,DIMENSION(klon,nbsrf),INTENT(IN)     :: pctsrf ! Pourcentage de sol f(nature du sol)
     79    REAL,DIMENSION(klon,nbsrf),INTENT(IN)     :: ftsol  ! Temperature du sol (surf)(Kelvin)
     80    REAL,DIMENSION(klon,klev,nbtr),INTENT(IN) :: tr_seri! Concentration Traceur [U/KgA] 
     81
    8082! Output variables
    8183    LOGICAL,DIMENSION(nbtr), INTENT(OUT) :: aerosol
     
    150152    END IF
    151153
     154!
     155! Initialisation de module carbon_cycle_mod
     156! ----------------------------------------------
     157    IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
     158       CALL carbon_cycle_init(tr_seri, aerosol, radio)
     159    END IF
     160
    152161  END SUBROUTINE traclmdz_init
    153162
     
    161170    USE dimphy
    162171    USE infotrac
     172    USE carbon_cycle_mod, ONLY : carbon_cycle, carbon_cycle_tr, carbon_cycle_cpl
    163173   
    164174    IMPLICIT NONE
     
    199209    REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: pctsrf ! Pourcentage de sol f(nature du sol)
    200210
     211
    201212! InOutput argument
    202213    REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT)  :: tr_seri ! Concentration Traceur [U/KgA] 
     
    206217    REAL,DIMENSION(klon,nbtr), INTENT(OUT)        :: source  ! a voir lorsque le flux de surface est prescrit
    207218    REAL,DIMENSION(klon,klev,nbtr), INTENT(OUT)   :: d_tr_cl ! Td couche limite/traceur
    208 
    209219
    210220!=======================================================================================
     
    301311    END DO
    302312
     313!======================================================================
     314!   Calcul de cycle de carbon
     315!======================================================================
     316    IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
     317       CALL carbon_cycle(nstep, pdtphys, pctsrf, tr_seri)
     318    END IF
     319
    303320  END SUBROUTINE traclmdz
    304321
Note: See TracChangeset for help on using the changeset viewer.