Ignore:
Timestamp:
Sep 4, 2018, 1:39:46 PM (6 years ago)
Author:
oboucher
Message:

Adding the reading of flag level_coupling_esm needed for the ESM version
Cleaning up the conf_phys_m.F90 routine with no further change

Location:
LMDZ6/trunk/libf/phylmd
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.F90

    r2351 r3384  
    11MODULE carbon_cycle_mod
     2
     3!=======================================================================
     4!
     5!   Authors: Patricia Cadule and Laurent Fairhead
     6!            base sur un travail anterieur mene par Patricia Cadule et Josefine
     7!            Ghattas
     8!   -------
     9!
     10!  Purpose and description:
     11!  -----------------------
    212! Controle module for the carbon CO2 tracers :
    313!   - Identification
     
    616!   - Calculate new carbon flux for sending to coupled models (PISCES and ORCHIDEE)
    717!
    8 ! Author : Josefine GHATTAS, Patricia CADULE
     18! Module permettant de mettre a jour les champs (puits et sources) pour le transport de CO2 en
     19! online (IPSL-CM et LMDZOR) et offline (lecture de carte)
     20!   
     21! Le cas online/offline est defini par le flag carbon_cycle_cpl (y/n)
     22! Le transport du traceur CO2 est defini par le flag carbon_cycle_tr (y/n)
     23! la provenance des champs (termes de puits) est denini par le flag  level_coupling_esm
     24
     25! level_coupling_esm : level of coupling of the biogeochemical fields between
     26! LMDZ, ORCHIDEE and NEMO
     27! Definitions of level_coupling_esm in physiq.def
     28! level_coupling_esm = 0  ! No field exchange between LMDZ and ORCHIDEE models
     29!                         ! No field exchange between LMDZ and NEMO
     30! level_coupling_esm = 1  ! Field exchange between LMDZ and ORCHIDEE models
     31!                         ! No field exchange between LMDZ and NEMO models
     32! level_coupling_esm = 2  ! No field exchange between LMDZ and ORCHIDEE models
     33!                         ! Field exchange between LMDZ and NEMO models
     34! level_coupling_esm = 3  ! Field exchange between LMDZ and ORCHIDEE models
     35!                         ! Field exchange between LMDZ and NEMO models
     36!
     37! si carbon_cycle_cpl=y alors les termes de puits et sources sont mis a jour
     38! en focntion de la valeur de level_coupling_esm
     39! dans tous les cas  (si carbon_cycle_cpl=y) les valeurs des emissions anthropiques de CO2 (fossil
     40! fuel+cement) sont lues,
     41! - soit via des cartes 2D mensuelles (fichiers netcdf contenant 12 valeurs par
     42! annee): fCO2_fco2fos
     43! - soit via des fichier txt contenant une valeur globale mensuelle/annuelle: fCO2_fco2fos_1D
     44!
     45! Ce module permet de transport des champs de carbone dans LMDz
     46
     47! Declaration des differents champs
     48! LAND: fCO2_nep, fCO2_fLuc, fCO2_fFire,
     49! OCEAN: fCO2_fgco2
     50! FOS:fCO2_fco2fos
    951
    1052  IMPLICIT NONE
     
    1860  LOGICAL, PUBLIC :: carbon_cycle_cpl       ! Coupling of CO2 fluxes between LMDZ/ORCHIDEE and LMDZ/OCEAN(PISCES)
    1961!$OMP THREADPRIVATE(carbon_cycle_cpl)
     62  INTEGER, SAVE, PUBLIC :: level_coupling_esm
     63!$OMP THREADPRIVATE(level_coupling_esm)
    2064
    2165  LOGICAL :: carbon_cycle_emis_comp_omp=.FALSE.
     
    2771!$OMP THREADPRIVATE(RCO2_inter)
    2872
    29 ! Scalare values when no transport, from physiq.def
    30   REAL :: fos_fuel_s_omp
    31   REAL :: fos_fuel_s  ! carbon_cycle_fos_fuel dans physiq.def
    32 !$OMP THREADPRIVATE(fos_fuel_s)
     73! Scalar values when no transport, from physiq.def
     74  REAL :: fCO2_fco2fos_1D_omp
     75!$OMP THREADPRIVATE(fCO2_fco2fos_1D_omp)
     76  REAL :: fCO2_fco2fos_1D  ! carbon_cycle_fco2fos dans physiq.def
     77!$OMP THREADPRIVATE(fCO2_fco2fos_1D)
    3378  REAL :: emis_land_s ! not yet implemented
    3479!$OMP THREADPRIVATE(emis_land_s)
     
    3782!$OMP THREADPRIVATE(airetot)
    3883
    39   INTEGER :: ntr_co2  ! Number of tracers concerning the carbon cycle
     84  INTEGER :: ntr_co2  ! Number of fields concerning the carbon cycle
    4085!$OMP THREADPRIVATE(ntr_co2)
    4186
    42 ! fco2_ocn_day : flux CO2 from ocean for 1 day (cumulated) [gC/m2/d]. Allocation and initalization done in cpl_mod
    43   REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocn_day
    44 !$OMP THREADPRIVATE(fco2_ocn_day)
    45 
    46   REAL, DIMENSION(:), ALLOCATABLE :: fco2_land_day   ! flux CO2 from land for 1 day (cumulated)  [gC/m2/d]
    47 !$OMP THREADPRIVATE(fco2_land_day)
    48   REAL, DIMENSION(:), ALLOCATABLE :: fco2_lu_day     ! Emission from land use change for 1 day (cumulated) [gC/m2/d]
    49 !$OMP THREADPRIVATE(fco2_lu_day)
     87! fCO2_fgco2 : carbon flux from ocean cumulated between 2 ATM-OCN coupling timestep [gC/m2/Dt].
     88! fCO2_fgco2 :  flux de carbone venant de l ocean. Ce flux est cumule entre
     89! deux pas de temps du couplage ATM-OCN [gC/m2/Dt].
     90! Allocation and initalization done in cpl_mod
     91
     92! OCEAN
     93! fkux echange a la frequence de couplage entre NEMO et LMDZ
     94  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fCO2_fgco2
     95!$OMP THREADPRIVATE(fCO2_fgco2)
     96
     97! LAND
     98  REAL, DIMENSION(:), ALLOCATABLE :: fCO2_nbp        ! carbon flux from land at each time step  [kgC/m2/s]
     99!$OMP THREADPRIVATE(fCO2_nbp)
     100  REAL, DIMENSION(:), ALLOCATABLE :: fCO2_nep        ! carbon flux from land at each time step  [kgC/m2/s]
     101!$OMP THREADPRIVATE(fCO2_nep)
     102  REAL, DIMENSION(:), ALLOCATABLE :: fCO2_fLuc     ! Emission from land use change  [gC/m2/s]
     103!$OMP THREADPRIVATE(fCO2_fLuc)
     104  REAL, DIMENSION(:), ALLOCATABLE :: fCO2_fFire
     105!$OMP THREADPRIVATE(fCO2_fFire)
     106
     107! SOURCES: FOSSIL FUEL emissions
     108  REAL, DIMENSION(:), ALLOCATABLE :: fCO2_fco2fos
     109!$OMP THREADPRIVATE(fCO2_fco2fos)
    50110
    51111  REAL, DIMENSION(:,:), ALLOCATABLE :: dtr_add       ! Tracer concentration to be injected
    52112!$OMP THREADPRIVATE(dtr_add)
    53 
    54 ! Following 2 fields will be allocated and initialized in surf_land_orchidee
    55   REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_land_inst  ! flux CO2 from land at one time step
    56 !$OMP THREADPRIVATE(fco2_land_inst)
    57   REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_lu_inst    ! Emission from land use change at one time step
    58 !$OMP THREADPRIVATE(fco2_lu_inst)
    59 
    60 ! Calculated co2 field to be send to the ocean via the coupler and to ORCHIDEE
     113  REAL, DIMENSION(:), ALLOCATABLE :: dtr_add_sum       ! Tracer concentration to be injected
     114!$OMP THREADPRIVATE(dtr_add_sum)
     115
     116! Following 4 fields will be allocated and initialized in surf_land_orchidee
     117  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fCO2_nbp_inst  ! flux CO2 from land at one time step
     118!$OMP THREADPRIVATE(fCO2_nbp_inst)
     119  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fCO2_nep_inst  ! flux CO2 from land at one time step
     120!$OMP THREADPRIVATE(fCO2_nep_inst)
     121  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fCO2_fLuc_inst    ! Emission from land use change at one time step
     122!$OMP THREADPRIVATE(fCO2_fLuc_inst)
     123  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fCO2_fFire_inst  ! flux CO2 from land at one time step
     124!$OMP THREADPRIVATE(fCO2_fFire_inst)
     125
     126! Calculated co2 field to be send to the ocean model (NEMO) via the coupler and to the land surface model (ORCHIDEE)
    61127  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: co2_send ! Field allocated in phyetat0
    62128!$OMP THREADPRIVATE(co2_send)
    63129
    64130
    65   TYPE, PUBLIC ::   co2_trac_type
    66      CHARACTER(len = 8) :: name       ! Tracer name in tracer.def
     131  TYPE, PUBLIC ::   co2_fields_type
     132     CHARACTER(len = 20) :: name       ! Fields
    67133     INTEGER            :: id         ! Index in total tracer list, tr_seri
    68134     CHARACTER(len=30)  :: file       ! File name
     
    72138     INTEGER            :: readstep   ! Actual time step to read in file
    73139     LOGICAL            :: updatenow  ! True if this tracer should be updated this time step
     140  END TYPE co2_fields_type
     141  INTEGER,PARAMETER :: maxco2fields=5  ! Maximum number of different CO2 fluxes
     142  TYPE(co2_fields_type), DIMENSION(maxco2fields) :: co2fields
     143!$OMP THREADPRIVATE(co2fields)
     144
     145
     146  TYPE, PUBLIC ::   co2_trac_type
     147     CHARACTER(len = 8) :: name       ! Tracer name in tracer.def
     148     INTEGER            :: id         ! Index in total tracer list, tr_seri
     149     CHARACTER(len=30)  :: file       ! File name
     150     LOGICAL            :: cpl        ! True if this tracers is coupled from ORCHIDEE or PISCES.
     151                                      ! False if read from file.
     152     INTEGER            :: updatefreq ! Frequence to inject in second
     153     INTEGER            :: readstep   ! Actual time step to read in file
     154     LOGICAL            :: updatenow  ! True if this tracer should be updated this time step
    74155  END TYPE co2_trac_type
    75156  INTEGER,PARAMETER :: maxco2trac=5  ! Maximum number of different CO2 fluxes
    76157  TYPE(co2_trac_type), DIMENSION(maxco2trac) :: co2trac
     158
     159
    77160
    78161CONTAINS
     
    93176    USE phys_cal_mod, ONLY : mth_len
    94177    USE print_control_mod, ONLY: lunout
     178    USE infocfields_mod
    95179
    96180    IMPLICIT NONE
     
    116200    IF (.NOT. carbon_cycle_tr) THEN
    117201!$OMP MASTER
    118        fos_fuel_s_omp = 0.
    119        CALL getin ('carbon_cycle_fos_fuel',fos_fuel_s_omp)
     202       fCO2_fco2fos_1D_omp = 0.
     203       CALL getin ('carbon_cycle_fco2fos_1D',fCO2_fco2fos_1D_omp)
    120204!$OMP END MASTER
    121205!$OMP BARRIER
    122        fos_fuel_s=fos_fuel_s_omp
    123        WRITE(lunout,*) 'carbon_cycle_fos_fuel = ', fos_fuel_s
     206       fCO2_fco2fos_1D=fCO2_fco2fos_1D_omp
     207       CALL bcast(fCO2_fco2fos_1D)
     208       WRITE(lunout,*) 'carbon_cycle_fco2fos_1D = ', fCO2_fco2fos_1D
    124209    END IF
    125210
     
    153238
    154239
    155 ! 2) Search for carbon tracers and set default values
     240! 2) Search for carbon fields and set default values
    156241! ---------------------------------------------------
    157242    itc=0
    158     DO it=1,nbtr
    159 !!       iiq=niadv(it+2)                                                            ! jyg
    160        iiq=niadv(it+nqo)                                                            ! jyg
    161        
    162        SELECT CASE(tname(iiq))
    163        CASE("fCO2_ocn")
     243    DO it=1,nbcf_in  ! bien remplir le fichier pour avoir un champ fos et un champs ocean
     244
     245!fCO2_nbp, fCO2_nep, fCO2_fLuc, fCO2_fFire, fCO2_fco2fos, fCO2_fgco2       
     246
     247       SELECT CASE(cfname_in(it))
     248       !SELECT CASE(co2fields(it)%name)
     249       CASE("fCO2_fgco2")
    164250          itc = itc + 1
    165           co2trac(itc)%name='fCO2_ocn'
    166           co2trac(itc)%id=it
    167           co2trac(itc)%file='fl_co2_ocean.nc'
    168           IF (carbon_cycle_cpl .AND. type_ocean=='couple') THEN
    169              co2trac(itc)%cpl=.TRUE.
    170              co2trac(itc)%updatefreq = 86400 ! Once a day as the coupling with OASIS/PISCES
     251          co2fields(it)%name=TRIM(cfname_in(it))
     252          co2fields(it)%id=it
     253          co2fields(it)%file='flx_fgco2_ocean.nc'
     254          IF (carbon_cycle_cpl .AND. (type_ocean=='couple') .AND. (level_coupling_esm.GE.2))  THEN
     255             WRITE(lunout,*) 'carbon_cycle_mod (ESM) --- fCO2_fgco2'
     256             co2fields(it)%cpl=.TRUE.
     257! >> PC
     258! on va injecter a tous les pas de temps de couplage (2700x2)
     259! recuperer proprement la frequence de couplage
     260! << PC
     261!!!! METTRE la vraie frequence de couplage !!! PAS en dur
     262             co2fields(it)%updatefreq = 5400 !  OASIS/NEMO-PISCES
     263! << PC
     264          ELSE IF (carbon_cycle_cpl .AND.  (level_coupling_esm.LE.2))  THEN
     265             co2fields(it)%cpl=.FALSE.
     266             co2fields(it)%updatefreq = 86400*mth_len ! Once a month
     267          END IF
     268       CASE("fCO2_nbp")
     269          itc = itc + 1
     270          co2fields(it)%name=TRIM(cfname_in(it))
     271          co2fields(it)%id=it
     272          co2fields(it)%file='flx_nbp_land.nc'
     273          IF (carbon_cycle_cpl .AND. ((level_coupling_esm.EQ.1) .OR. level_coupling_esm.EQ.3)) THEN
     274             WRITE(lunout,*) 'carbon_cycle_mod (ESM) --- fCO2_nbp'
     275             co2fields(it)%cpl=.TRUE.
     276             co2fields(it)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
     277          ELSE IF (carbon_cycle_cpl .AND. ((level_coupling_esm.EQ.0) .OR.  level_coupling_esm.EQ.2)) THEN
     278             co2fields(it)%cpl=.FALSE.
     279!             co2fields(itc)%updatefreq = 10800   ! 10800sec = 3H
     280             co2fields(it)%updatefreq = 86400*mth_len ! Once a month
     281          END IF
     282!!!! Si le test est ok pour nbp dupliquer sur les autres champs LAND
     283       CASE("fCO2_nep")
     284          itc = itc + 1
     285          co2fields(it)%name=TRIM(cfname_in(it))
     286          co2fields(it)%id=it
     287          co2fields(it)%file='flx_nep_land.nc'
     288          IF (carbon_cycle_cpl .AND. ok_veget) THEN
     289             WRITE(lunout,*) 'carbon_cycle_mod (ESM) --- fCO2_nep'
     290             co2fields(it)%cpl=.TRUE.
     291             co2fields(it)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
    171292          ELSE
    172              co2trac(itc)%cpl=.FALSE.
    173              co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
     293             co2fields(it)%cpl=.FALSE.
     294!             co2fields(itc)%updatefreq = 10800   ! 10800sec = 3H
     295             co2fields(it)%updatefreq = 86400*mth_len ! Once a month
    174296          END IF
    175        CASE("fCO2_land")
     297       CASE("fCO2_fLuc")
    176298          itc = itc + 1
    177           co2trac(itc)%name='fCO2_land'
    178           co2trac(itc)%id=it
    179           co2trac(itc)%file='fl_co2_land.nc'
     299          co2fields(it)%name=TRIM(cfname_in(it))
     300          co2fields(it)%id=it
     301          co2fields(it)%file='flx_fLuc_land.nc'
    180302          IF (carbon_cycle_cpl .AND. ok_veget) THEN
    181              co2trac(itc)%cpl=.TRUE.
    182              co2trac(itc)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
     303             WRITE(lunout,*) 'carbon_cycle_mod (ESM) --- fCO2_nbp'
     304             co2fields(it)%cpl=.TRUE.
     305             co2fields(it)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
    183306          ELSE
    184              co2trac(itc)%cpl=.FALSE.
    185 !             co2trac(itc)%updatefreq = 10800   ! 10800sec = 3H
    186              co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
     307             co2fields(it)%cpl=.FALSE.
     308             co2fields(it)%updatefreq = 10800   ! 10800sec = 3H
    187309          END IF
    188        CASE("fCO2_land_use")
     310       CASE("fCO2_fco2fos")
    189311          itc = itc + 1
    190           co2trac(itc)%name='fCO2_land_use'
    191           co2trac(itc)%id=it
    192           co2trac(itc)%file='fl_co2_land_use.nc'
    193           IF (carbon_cycle_cpl .AND. ok_veget) THEN
    194              co2trac(it)%cpl=.TRUE.
    195              co2trac(itc)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
    196           ELSE
    197              co2trac(itc)%cpl=.FALSE.
    198              co2trac(itc)%updatefreq = 10800   ! 10800sec = 3H
    199           END IF
    200        CASE("fCO2_fos_fuel")
     312          !co2fields(it)%name='fCO2_fco2fos'
     313          co2fields(it)%name=TRIM(cfname_in(it))
     314          co2fields(it)%id=it
     315          co2fields(it)%file='fco2fos.nc'
     316! >> PC
     317         IF ( carbon_cycle_cpl .AND. carbon_cycle_tr) THEN
     318          WRITE(lunout,*) 'carbon_cycle_mod (ESM) --- fCO2_fco2fos'
     319          co2fields(it)%cpl=.TRUE.
     320          co2fields(it)%updatefreq = 86400*mth_len ! Once a month
     321         ELSE IF ( carbon_cycle_cpl .AND. (.NOT. carbon_cycle_tr)) THEN
     322          co2fields(it)%cpl=.TRUE.
     323          co2fields(it)%updatefreq = 86400*mth_len ! Once a month
     324            WRITE(*,*) "lecture du champs scalaire"
     325         END IF
     326! << PC
     327       CASE("fCO2_fFire")
    201328          itc = itc + 1
    202           co2trac(itc)%name='fCO2_fos_fuel'
    203           co2trac(itc)%id=it
    204           co2trac(itc)%file='fossil_fuel.nc'
    205           co2trac(itc)%cpl=.FALSE.       ! This tracer always read from file
    206 !         co2trac(itc)%updatefreq = 86400  ! 86400sec = 24H Cadule case
    207           co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
    208        CASE("fCO2_bbg")
    209           itc = itc + 1
    210           co2trac(itc)%name='fCO2_bbg'
    211           co2trac(itc)%id=it
    212           co2trac(itc)%file='fl_co2_bbg.nc'
    213           co2trac(itc)%cpl=.FALSE.       ! This tracer always read from file
    214           co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
     329          co2fields(it)%name=TRIM(cfname_in(it))
     330          co2fields(it)%id=it
     331          co2fields(it)%file='flx_fFire_land.nc'
     332          co2fields(it)%cpl=.FALSE.       ! This tracer always read from file
     333          co2fields(it)%updatefreq = 86400*mth_len ! Once a month
    215334       CASE("fCO2")
    216335          ! fCO2 : One tracer transporting the total CO2 flux
    217336          itc = itc + 1
    218           co2trac(itc)%name='fCO2'
    219           co2trac(itc)%id=it
    220           co2trac(itc)%file='fl_co2.nc'
     337          co2fields(it)%name='fCO2'
     338          co2fields(it)%id=it
     339          co2fields(it)%file='flx_fCO2.nc'
    221340          IF (carbon_cycle_cpl) THEN
    222              co2trac(itc)%cpl=.TRUE.
     341             WRITE(lunout,*) 'carbon_cycle_mod (ESM) --- fCO2'
     342             co2fields(it)%cpl=.TRUE.
    223343          ELSE
    224              co2trac(itc)%cpl=.FALSE.
     344             co2fields(it)%cpl=.FALSE.
    225345          END IF
    226           co2trac(itc)%updatefreq = 86400
     346          co2fields(it)%updatefreq = 86400*mth_len
    227347          ! DOES THIS WORK ???? Problematic due to implementation of the coupled fluxes...
    228348          CALL abort_physic('carbon_cycle_init','transport of total CO2 has to be implemented and tested',1)
     
    230350    END DO
    231351
    232     ! Total number of carbon CO2 tracers
    233     ntr_co2 = itc
    234    
     352    ! CO2 tracer
     353
     354IF ( carbon_cycle_cpl .AND. carbon_cycle_tr) THEN
     355    itc=0
     356
     357    DO it=1,nbtr
     358       iiq=niadv(it+nqo)
     359
     360       SELECT CASE(tname(iiq))
     361       CASE("fCO2")
     362          itc = itc + 1
     363          co2fields(it)%name='fCO2'
     364          IF (carbon_cycle_cpl .AND. type_ocean=='couple') THEN
     365             co2fields(it)%cpl=.TRUE.
     366          END IF
     367        END SELECT
     368     END DO
     369END IF
     370
     371!!!!! BIEN FAIRE LA DIFFERENCE ENTRE tracer.def et coupling_fields.def
     372! cela conditionne la valeur de ntr_co2
     373!    ntr_co2 = itc
     374
     375    ntr_co2=0
     376    IF (carbon_cycle_tr .AND. (nbcf .GT. 0)) ntr_co2=1   
     377
    235378    ! Definition of control varaiables for the tracers
    236379    DO it=1,ntr_co2
     
    247390! ---------------------
    248391    ! Allocate vector for storing fluxes to inject
    249     ALLOCATE(dtr_add(klon,maxco2trac), stat=ierr)
     392!fCO2_nbp, fCO2_nep, fCO2_fLuc, fCO2_fFire, fCO2_fco2fos, fCO2_fgco2
     393    ALLOCATE(dtr_add(klon,maxco2fields), stat=ierr)
    250394    IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 11',1)       
    251    
     395
     396    ALLOCATE(dtr_add_sum(klon), stat=ierr)
     397    IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 12',1)   
     398
     399 
    252400    ! Allocate variables for cumulating fluxes from ORCHIDEE
    253     IF (RCO2_inter) THEN
    254        IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
    255           ALLOCATE(fco2_land_day(klon), stat=ierr)
     401!    IF (RCO2_inter) THEN
     402       !IF ((.NOT. carbon_cycle_tr) .AND. carbon_cycle_cpl) THEN
     403       IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
     404
     405          ALLOCATE(fCO2_nbp(klon), stat=ierr)
    256406          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 2',1)
    257           fco2_land_day(1:klon) = 0.
     407          fCO2_nbp(1:klon) = 0.
     408
     409          ALLOCATE(fCO2_nep(klon), stat=ierr)
     410          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 2',1)
     411          fCO2_nep(1:klon) = 0.
    258412         
    259           ALLOCATE(fco2_lu_day(klon), stat=ierr)
     413          ALLOCATE(fCO2_fLuc(klon), stat=ierr)
    260414          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 3',1)
    261           fco2_lu_day(1:klon)   = 0.
     415          fCO2_fLuc(1:klon)   = 0.
     416
     417          ALLOCATE(fCO2_fFire(klon), stat=ierr)
     418          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 2',1)
     419          fCO2_fFire(1:klon) = 0.
     420
    262421       END IF
    263     END IF
     422!    END IF
    264423
    265424
     
    282441    END DO
    283442
    284     IF (ntr_co2==0) THEN
     443
     444    IF (ntr_co2==0 .AND. carbon_cycle_tr) THEN
    285445       ! No carbon tracers found in tracer.def. It is not possible to do carbon cycle
    286        WRITE(lunout,*) 'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cp'
     446! >> PC
     447       WRITE(lunout,*) 'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cpl'
     448! << PC
    287449       CALL abort_physic('carbon_cycle_init', 'No carbon tracers found in tracer.def',1)
    288450    END IF
     
    312474    USE print_control_mod, ONLY: lunout
    313475    USE geometry_mod, ONLY : cell_area
     476    USE infocfields_mod
     477
     478! >> PC
     479! ne pas le mettre en argument de la subrourine
     480!    USE time_phylmdz_mod, ONLY: pdtphys
     481! << PC
    314482
    315483    IMPLICIT NONE
     
    326494
    327495! Local variables
    328     INTEGER :: it
     496    INTEGER :: it,itc
     497! >> PC
     498    LOGICAL :: newyear ! indicates if a new month just started
     499! << PC
    329500    LOGICAL :: newmonth ! indicates if a new month just started
    330501    LOGICAL :: newday   ! indicates if a new day just started
    331502    LOGICAL :: endday   ! indicated if last time step in a day
    332503
    333     REAL, PARAMETER :: fact=1.E-15/2.12  ! transformation factor from gC/m2/day => ppm/m2/day
     504! >> PC
     505    REAL, PARAMETER :: fact=1.0e06  * 28.97/44.011  ! transformation factor kg CO2/kg air => ppm
     506! << PC
    334507    REAL, DIMENSION(klon) :: fco2_tmp
    335508    REAL :: sumtmp
     
    340513! -------------------------------------------------------------------------------------------------------
    341514
    342     newday = .FALSE.; endday = .FALSE.; newmonth = .FALSE.
     515! >> PC
     516! Mise a jour mensuelle des emissions fossiles
     517    !newday = .FALSE.; endday = .FALSE.; newmonth = .FALSE.
     518    newday = .FALSE.; endday = .FALSE.; newmonth = .FALSE. ; newyear = .FALSE.
    343519
    344520    IF (MOD(nstep,INT(86400./pdtphys))==1) newday=.TRUE.
    345521    IF (MOD(nstep,INT(86400./pdtphys))==0) endday=.TRUE.
    346522    IF (newday .AND. day_cur==1) newmonth=.TRUE.
     523! mettre la duree de l annee au propre len_year ???
     524    IF (newday .AND. (MOD(nstep,INT(86400.*365/pdtphys))==1)) newyear=.TRUE.
     525! << PC
    347526
    348527! 2)  For each carbon tracer find out if it is time to inject (update)
    349528! --------------------------------------------------------------------
    350     DO it = 1, ntr_co2
    351        IF ( MOD(nstep,INT(co2trac(it)%updatefreq/pdtphys)) == 1 ) THEN
    352           co2trac(it)%updatenow = .TRUE.
     529    !DO it = 1, nbcf_in+2
     530    DO it = 1, nbcf_in
     531       WRITE(lunout,*) 'nstep ',nstep
     532       WRITE(lunout,*) 'co2fields(it)%updatefreq ',co2fields(it)%name,' ', co2fields(it)%updatefreq
     533       WRITE(lunout,*) 'co2fields(it)%name ',co2fields(it)%name
     534       WRITE(lunout,*) 'INT(pdtphys) ',INT(pdtphys)
     535       WRITE(lunout,*) '(INT(co2fields(it)%updatefreq)/INT(pdtphys))', (INT(co2fields(it)%updatefreq)/INT(pdtphys))
     536       WRITE(lunout,*) 'MOD(nstep,(INT(co2fields(it)%updatefreq)/INT(pdtphys))) ',MOD(nstep,(INT(co2fields(it)%updatefreq)/INT(pdtphys)))
     537       IF ( MOD(nstep,(INT(co2fields(it)%updatefreq)/INT(pdtphys))) == 0 ) THEN
     538         co2fields(it)%updatenow = .TRUE.
    353539       ELSE
    354           co2trac(it)%updatenow = .FALSE.
     540         co2fields(it)%updatenow = .FALSE.
    355541       END IF
     542       WRITE(lunout,*) 'co2fields(it)%updatenow ',co2fields(it)%updatenow
    356543    END DO
    357544
    358545! 3) Get tracer update
    359546! --------------------------------------
    360     DO it = 1, ntr_co2
    361        IF ( co2trac(it)%updatenow ) THEN
    362           IF ( co2trac(it)%cpl ) THEN
     547! >> PC
     548       IF (newyear) THEN
     549         co2fields(:)%readstep = 0
     550       END IF
     551! << PC
     552
     553    DO it = 1, nbcf_in
     554       IF ( co2fields(it)%updatenow ) THEN
     555          IF ( co2fields(it)%cpl ) THEN
    363556             ! Get tracer from coupled model
    364              SELECT CASE(co2trac(it)%name)
    365              CASE('fCO2_land')     ! from ORCHIDEE
    366                 dtr_add(:,it) = fco2_land_inst(:)*pctsrf(:,is_ter)*fact ! [ppm/m2/day]
    367              CASE('fCO2_land_use') ! from ORCHIDEE
    368                 dtr_add(:,it) = fco2_lu_inst(:)  *pctsrf(:,is_ter)*fact ! [ppm/m2/day]
    369              CASE('fCO2_ocn')      ! from PISCES
    370                 dtr_add(:,it) = fco2_ocn_day(:)  *pctsrf(:,is_oce)*fact ! [ppm/m2/day]
     557             SELECT CASE(TRIM(co2fields(it)%name))
     558             CASE('fCO2_nbp')     ! from ORCHIDEE
     559                dtr_add(:,it) = fCO2_nbp_inst(:)*pctsrf(:,is_ter)*((co2fields(it)%updatefreq)/INT(pdtphys))*fact !  [ppm/m2/s]
     560             CASE('fCO2_nep')     ! from ORCHIDEE
     561                dtr_add(:,it) = fCO2_nep_inst(:)*pctsrf(:,is_ter)*((co2fields(it)%updatefreq)/INT(pdtphys))*fact ! [ppm/m2/s]
     562             CASE('fCO2_fLuc') ! from ORCHIDEE
     563                dtr_add(:,it) = fCO2_fLuc_inst(:)  *pctsrf(:,is_ter)*((co2fields(it)%updatefreq)/INT(pdtphys))*fact ! [ppm/m2/s]
     564             CASE('fCO2_fFire')     ! from ORCHIDEE
     565                dtr_add(:,it) = fCO2_fFire_inst(:)*pctsrf(:,is_ter)*((co2fields(it)%updatefreq)/INT(pdtphys))*fact !  [ppm/m2/s]
     566             CASE('fCO2_fgco2')      ! from PISCES
     567                dtr_add(:,it) = fCO2_fgco2(:)  *pctsrf(:,is_oce)*((co2fields(it)%updatefreq)/INT(pdtphys))*fact ! [ppm/m2/s]
     568! >> PC
     569             CASE("fCO2_fco2fos")
     570               WRITE(lunout,*) 'carbon cycle --- fossil fuel emissions'
     571                 IF (newmonth) THEN
     572                   co2fields(it)%readstep = co2fields(it)%readstep + 1
     573! ne pas faire la lecture du fichier a chaque pas de temps
     574                   CALL read_map2D(co2fields(it)%file,'CO2_em_anthro',co2fields(it)%readstep,.TRUE.,source(1:klon,co2fields(it)%id))
     575                   dtr_add(:,it) = source(1:klon,co2fields(it)%id)*pctsrf(:,is_ter)*(co2fields(it)%updatefreq/INT(pdtphys))*fact ! [ppm/m2/s]
     576                 END IF
     577! << PC             
    371578             CASE DEFAULT
    372                 WRITE(lunout,*) 'Error with tracer ',co2trac(it)%name
     579                WRITE(lunout,*) 'Error with field ',co2fields(it)%name
    373580                CALL abort_physic('carbon_cycle', 'No coupling implemented for this tracer',1)
    374581             END SELECT
    375582          ELSE
    376583             ! Read tracer from file
    377              co2trac(it)%readstep = co2trac(it)%readstep + 1 ! increment time step in file
    378 ! Patricia   CALL read_map2D(co2trac(it)%file,'fco2',co2trac(it)%readstep,.FALSE.,dtr_add(:,it))
    379              CALL read_map2D(co2trac(it)%file,'fco2',co2trac(it)%readstep,.TRUE.,dtr_add(:,it))
    380 
    381              ! Converte from kgC/m2/h to kgC/m2/s
    382              dtr_add(:,it) = dtr_add(:,it)/3600
     584             co2fields(it)%readstep = co2fields(it)%readstep + 1 ! increment time step in file
     585! Patricia   CALL read_map2D(co2fields(it)%file,'fco2',co2fields(it)%readstep,.FALSE.,dtr_add(:,it))
     586             CALL read_map2D(co2fields(it)%file,'fco2',co2fields(it)%readstep,.TRUE.,dtr_add(:,it))
     587
     588! >> PC
     589             !! Converte from kgC/m2/h to kgC/m2/s
     590             !dtr_add(:,it) = dtr_add(:,it)/3600
     591! << PC
    383592             ! Add individual treatment of values read from file
    384              SELECT CASE(co2trac(it)%name)
    385              CASE('fCO2_land')
     593             SELECT CASE(co2fields(it)%name)
     594             CASE('fCO2_nbp')
    386595                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
    387              CASE('fCO2_land_use')
     596             CASE('fCO2_nep')
    388597                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
    389              CASE('fCO2_ocn')
     598             CASE('fCO2_fLuc')
     599                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
     600             CASE('fCO2_fFire')
     601                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
     602             CASE('fCO2_fgco2')
    390603                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_oce)
     604             CASE('fCO2_fco2fos')
     605                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
    391606! Patricia :
    392607!             CASE('fCO2_fos_fuel')
    393608!                dtr_add(:,it) = dtr_add(:,it)/mth_len
    394 !                co2trac(it)%readstep = 0 ! Always read same value for fossil fuel(Cadule case)
     609!                co2fields(it)%readstep = 0 ! Always read same value for fossil fuel(Cadule case)
    395610             END SELECT
    396611          END IF
     
    402617! ------------------------------------------------------------------
    403618    IF (carbon_cycle_tr) THEN
     619 
     620      dtr_add_sum(1:klon)=0.
     621      DO it=1,nbcf_in
     622         dtr_add_sum(1:klon)=dtr_add_sum(1:klon)+dtr_add(1:klon,it)
     623      END DO
     624 
    404625       DO it = 1, ntr_co2
    405           IF (.FALSE.) THEN
    406              tr_seri(1:klon,1,co2trac(it)%id) = tr_seri(1:klon,1,co2trac(it)%id) + dtr_add(1:klon,it)
    407              source(1:klon,co2trac(it)%id) = 0.
    408           ELSE
    409              source(1:klon,co2trac(it)%id) = dtr_add(1:klon,it)
    410           END IF
     626                 tr_seri(1:klon,1,co2trac(it)%id) = tr_seri(1:klon,1,co2trac(it)%id) + dtr_add_sum(1:klon)
    411627       END DO
    412628    END IF
     
    415631! 5) Calculations for new CO2 value for the radiation scheme(instead of reading value from .def)
    416632! ----------------------------------------------------------------------------------------------
    417     IF (RCO2_inter) THEN
    418        ! Cumulate fluxes from ORCHIDEE at each timestep
    419        IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
    420           IF (newday) THEN ! Reset cumulative variables once a day
    421              fco2_land_day(1:klon) = 0.
    422              fco2_lu_day(1:klon)   = 0.
    423           END IF
    424           fco2_land_day(1:klon) = fco2_land_day(1:klon) + fco2_land_inst(1:klon) ![gC/m2/day]
    425           fco2_lu_day(1:klon)   = fco2_lu_day(1:klon)   + fco2_lu_inst(1:klon)   ![gC/m2/day]
    426        END IF
    427 
    428        ! At the end of a new day, calculate a mean scalare value of CO2
    429        ! JG : Ici on utilise uniquement le traceur du premier couche du modele. Est-ce que c'est correcte ?
    430        IF (endday) THEN
     633    !IF (RCO2_inter) THEN
     634! >> PC
     635!       IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
     636!!          IF (newday) THEN ! Reset cumulative variables once a day
     637!!             fCO2_nep(1:klon) = 0.
     638!!             fCO2_fLuc(1:klon)   = 0.
     639!!          END IF
     640!! >> PC
     641!          fCO2_nep(1:klon) =  fCO2_nep_inst(1:klon) ![gC/m2/s]
     642!          fCO2_fLuc(1:klon)   =  fCO2_fLuc_inst(1:klon)   ![gC/m2/s]
     643!       END IF
     644!! << PC
     645
     646! >> PC
     647    !   IF (endday) THEN
     648! << PC
     649
     650! >> PC
     651! modifier le test (carbon_cycle_tr) ligne 492 pour prendre en compte que les cas
     652! ou carbon_cycle_cpl = 1 ou 2 .AND. carbon_cycle_tr=y
     653! bien declarer la variable fco2_tmp (pour un seul traceur)
    431654
    432655          IF (carbon_cycle_tr) THEN
     656          WRITE(lunout,*) 'fco2_tmp --- carbon_cycle_tr case'
    433657             ! Sum all co2 tracers to get the total delta CO2 flux
    434658             fco2_tmp(:) = 0.
     
    436660                fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2trac(it)%id)
    437661             END DO
    438              
    439           ELSE IF (carbon_cycle_cpl) THEN ! no carbon_cycle_tr
     662! << PC             
     663          ELSE IF (carbon_cycle_cpl .AND. (.NOT. carbon_cycle_tr)) THEN ! no carbon_cycle_tr
     664          WRITE(lunout,*) 'fco2_tmp --- carbon_cycle_cpl case'
    440665             ! Sum co2 fluxes comming from coupled models and parameter for fossil fuel
    441              fco2_tmp(1:klon) = fos_fuel_s + ((fco2_lu_day(1:klon) + fco2_land_day(1:klon))*pctsrf(1:klon,is_ter) &
    442                   + fco2_ocn_day(:)*pctsrf(:,is_oce)) * fact
     666! >> PC
     667             !fco2_tmp(1:klon) = (fCO2_fco2fos*pctsrf(1:klon,is_ter) + (fCO2_fLuc(1:klon) + fCO2_nep(1:klon))*pctsrf(1:klon,is_ter) &
     668
     669!             fco2_tmp(1:klon) = (fCO2_fco2fos(1:klon)*pctsrf(1:klon,is_ter) + fCO2_nbp(1:klon)*pctsrf(1:klon,is_ter) &
     670!                  + fCO2_fgco2(1:klon)*pctsrf(1:klon,is_oce)) * fact
     671! fCO2_fco2fos_1D
     672             fco2_tmp(:) = 0.
     673             fco2_tmp(:) =  ( fCO2_fco2fos_1D + fCO2_nbp_inst(:)*pctsrf(:,is_ter) + fCO2_fgco2(:)*pctsrf(:,is_oce))/2.12
     674             WRITE(lunout,*) 'fco2_tmp(:) ',fco2_tmp(:)
     675! << PC
    443676          END IF
    444677
    445678          ! Calculate a global mean value of delta CO2 flux
    446           fco2_tmp(1:klon) = fco2_tmp(1:klon) * cell_area(1:klon)
     679          fco2_tmp(:) = fco2_tmp(:) * cell_area(:)
    447680          CALL reduce_sum(SUM(fco2_tmp),sumtmp)
    448681          CALL bcast(sumtmp)
    449682          delta_co2_ppm = sumtmp/airetot
     683          WRITE(lunout,*) 'delta_co2_ppm: ',delta_co2_ppm
    450684         
    451685          ! Add initial value for co2_ppm and delta value
     686           WRITE(lunout,*)'carbon_cycle_mod --- co2_ppm0 ',co2_ppm0
    452687          co2_ppm = co2_ppm0 + delta_co2_ppm
    453          
     688          CALL bcast(co2_ppm)
     689          WRITE(lunout,*)'carbon_cycle_mod --- co2_ppm ',co2_ppm
     690IF (RCO2_inter) THEN         
    454691          ! Transformation of atmospheric CO2 concentration for the radiation code
    455692          RCO2 = co2_ppm * 1.0e-06  * 44.011/28.97
    456693         
    457           WRITE(lunout,*) 'RCO2 is now updated! RCO2 = ', RCO2
    458        END IF ! endday
    459 
    460     END IF ! RCO2_inter
     694          WRITE(lunout,*) 'RCO2 is now updated (in carbon_cycle_mod) ! RCO2 = ', RCO2
     695
     696! >> PC
     697    !   END IF ! endday
     698! << PC
     699
     700END IF ! RCO2_inter
    461701
    462702
    463703! 6) Calculate CO2 flux to send to ocean and land models : PISCES and ORCHIDEE         
    464704! ----------------------------------------------------------------------------
    465     IF (carbon_cycle_cpl) THEN
    466 
    467        IF (carbon_cycle_tr) THEN
    468           ! Sum all co2 tracers to get the total delta CO2 flux at first model layer
    469           fco2_tmp(:) = 0.
     705!    IF (carbon_cycle_cpl) THEN
     706!
     707!       IF (carbon_cycle_tr) THEN
     708!          ! Sum all co2 tracers to get the total delta CO2 flux at first model layer
     709!          fco2_tmp(:) = 0.
     710!          DO it = 1, ntr_co2
     711!             fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2fields(it)%id)         
     712!          END DO
     713!          co2_send(1:klon) = fco2_tmp(1:klon) + co2_ppm0
     714!       ELSE
     715!          ! Send a scalare value in 2D variable to ocean and land model (PISCES and ORCHIDEE)
     716!          co2_send(1:klon) = co2_ppm
     717!       END IF
     718!
     719!    END IF
     720
     721
     722! << PC
     723! co2_ppm0 au premier pas de temps
     724! prendre le co2 du restart
     725
     726       IF (carbon_cycle_cpl .AND. carbon_cycle_tr) THEN
     727          ! Sum all co2 tracers to get the total delta CO2 flux at first model
     728          ! layer
     729          !fco2_tmp(:) = 0.
    470730          DO it = 1, ntr_co2
    471              fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2trac(it)%id)
     731             fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2fields(it)%id)
    472732          END DO
    473733          co2_send(1:klon) = fco2_tmp(1:klon) + co2_ppm0
     734       ELSE IF (carbon_cycle_cpl .AND. (.NOT. carbon_cycle_tr)) THEN
     735          WRITE(lunout,*) 'carbon_cycle_mod --- co2_send(1:klon)', co2_send(1:klon)
     736          co2_send(1:klon) = co2_ppm
    474737       ELSE
    475           ! Send a scalare value in 2D variable to ocean and land model (PISCES and ORCHIDEE)
     738          ! Send a scalare value in 2D variable to ocean and land model (PISCES
     739          ! and ORCHIDEE)
    476740          co2_send(1:klon) = co2_ppm
    477741       END IF
    478742
    479     END IF
     743
    480744
    481745  END SUBROUTINE carbon_cycle
  • LMDZ6/trunk/libf/phylmd/conf_phys_m.F90

    r3378 r3384  
    2626    USE surface_data
    2727    USE phys_cal_mod
    28     USE carbon_cycle_mod,  ONLY: carbon_cycle_tr, carbon_cycle_cpl
     28    USE carbon_cycle_mod,  ONLY: carbon_cycle_tr, carbon_cycle_cpl, level_coupling_esm
    2929    USE mod_grid_phy_lmdz, ONLY: klon_glo
    3030    USE print_control_mod, ONLY: lunout
    3131
    32     include "conema3.h"
    33     include "fisrtilp.h"
    34     include "nuage.h"
    35     include "YOMCST.h"
    36     include "YOMCST2.h"
    37 
    38     include "thermcell.h"
    39 
     32    INCLUDE "conema3.h"
     33    INCLUDE "fisrtilp.h"
     34    INCLUDE "nuage.h"
     35    INCLUDE "YOMCST.h"
     36    INCLUDE "YOMCST2.h"
     37    INCLUDE "thermcell.h"
    4038
    4139    !IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
    42     include "clesphys.h"
    43     include "compbl.h"
    44     include "comsoil.h"
    45     include "YOEGWD.h"
     40    INCLUDE "clesphys.h"
     41    INCLUDE "compbl.h"
     42    INCLUDE "comsoil.h"
     43    INCLUDE "YOEGWD.h"
    4644    !
    4745    ! Configuration de la "physique" de LMDZ a l'aide de la fonction
     
    4947    !
    5048    ! LF 05/2001
    51     !
    52 
    5349    !
    5450    ! type_ocean:      type d'ocean (force, slab, couple)
     
    6763    ! bl95_b*: parameters in the formula to link CDNC to aerosol mass conc
    6864    !
    69 
    7065
    7166    ! Sortie:
     
    108103    REAL,SAVE           :: tau_cld_cv_omp, coefw_cld_cv_omp
    109104    INTEGER, SAVE       :: iflag_cld_cv_omp
    110 
    111105
    112106    REAL, SAVE          :: ratqshaut_omp
     
    201195    INTEGER, SAVE :: levout_histNMC_omp(3)
    202196    LOGICAL, SAVE :: ok_histNMC_omp(3)
    203     REAL, SAVE :: freq_outNMC_omp(3), freq_calNMC_omp(3)
     197    REAL, SAVE    :: freq_outNMC_omp(3), freq_calNMC_omp(3)
    204198    CHARACTER*4, SAVE :: type_run_omp
    205     LOGICAL,SAVE :: ok_cosp_omp, ok_airs_omp
    206     LOGICAL,SAVE :: ok_mensuelCOSP_omp,ok_journeCOSP_omp,ok_hfCOSP_omp
    207     REAL,SAVE :: lonmin_ins_omp, lonmax_ins_omp, latmin_ins_omp, latmax_ins_omp
    208     REAL,SAVE :: ecrit_hf_omp, ecrit_day_omp, ecrit_mth_omp, ecrit_reg_omp
    209     REAL,SAVE :: ecrit_ins_omp
    210     REAL,SAVE :: ecrit_LES_omp
    211     REAL,SAVE :: ecrit_tra_omp
    212     REAL,SAVE :: cvl_comp_threshold_omp
    213     REAL,SAVE :: cvl_sig2feed_omp
    214     REAL,SAVE :: cvl_corr_omp
    215     LOGICAL,SAVE :: ok_lic_melt_omp
    216     LOGICAL,SAVE :: ok_lic_cond_omp
    217     !
    218     INTEGER,SAVE :: iflag_cycle_diurne_omp
    219     LOGICAL,SAVE :: soil_model_omp,new_oliq_omp
    220     LOGICAL,SAVE :: ok_orodr_omp, ok_orolf_omp, ok_limitvrai_omp
     199    LOGICAL, SAVE :: ok_cosp_omp, ok_airs_omp
     200    LOGICAL, SAVE :: ok_mensuelCOSP_omp,ok_journeCOSP_omp,ok_hfCOSP_omp
     201    REAL, SAVE    :: lonmin_ins_omp, lonmax_ins_omp, latmin_ins_omp, latmax_ins_omp
     202    REAL, SAVE    :: ecrit_hf_omp, ecrit_day_omp, ecrit_mth_omp, ecrit_reg_omp
     203    REAL, SAVE    :: ecrit_ins_omp
     204    REAL, SAVE    :: ecrit_LES_omp
     205    REAL, SAVE    :: ecrit_tra_omp
     206    REAL, SAVE    :: cvl_comp_threshold_omp
     207    REAL, SAVE    :: cvl_sig2feed_omp
     208    REAL, SAVE    :: cvl_corr_omp
     209    LOGICAL, SAVE :: ok_lic_melt_omp
     210    LOGICAL, SAVE :: ok_lic_cond_omp
     211    !
     212    INTEGER, SAVE :: iflag_cycle_diurne_omp
     213    LOGICAL, SAVE :: soil_model_omp,new_oliq_omp
     214    LOGICAL, SAVE :: ok_orodr_omp, ok_orolf_omp, ok_limitvrai_omp
    221215    INTEGER, SAVE :: nbapp_rad_omp, iflag_con_omp
    222216    INTEGER, SAVE :: nbapp_cv_omp, nbapp_wk_omp
     
    231225    REAL, SAVE    :: sso_gkdrag_omp,sso_grahil_omp,sso_grcrit_omp
    232226    REAL, SAVE    :: sso_gfrcri_omp,sso_gkwake_omp,sso_gklift_omp
    233     LOGICAL,SAVE  :: ok_qch4_omp
    234     LOGICAL,SAVE  :: carbon_cycle_tr_omp
    235     LOGICAL,SAVE  :: carbon_cycle_cpl_omp
    236     LOGICAL,SAVE  :: adjust_tropopause_omp
    237     LOGICAL,SAVE  :: ok_daily_climoz_omp
     227    LOGICAL, SAVE :: ok_qch4_omp
     228    LOGICAL, SAVE :: carbon_cycle_tr_omp
     229    LOGICAL, SAVE :: carbon_cycle_cpl_omp
     230    INTEGER, SAVE :: level_coupling_esm_omp
     231    LOGICAL, SAVE :: adjust_tropopause_omp
     232    LOGICAL, SAVE :: ok_daily_climoz_omp
    238233
    239234    INTEGER, INTENT(OUT):: read_climoz ! read ozone climatology, OpenMP shared
     
    21482143    carbon_cycle_cpl_omp=.FALSE.
    21492144    CALL getin('carbon_cycle_cpl',carbon_cycle_cpl_omp)
     2145
     2146    ! >> PC
     2147    ! level_coupling_esm : level of coupling of the biogeochemical fields between LMDZ, ORCHIDEE and NEMO
     2148    ! Definitions of level_coupling_esm in physiq.def
     2149    ! level_coupling_esm = 0  ! No field exchange between LMDZ and ORCHIDEE models
     2150    !                         ! No field exchange between LMDZ and NEMO
     2151    ! level_coupling_esm = 1  ! Field exchange between LMDZ and ORCHIDEE models
     2152    !                         ! No field exchange between LMDZ and NEMO models
     2153    ! level_coupling_esm = 2  ! No field exchange between LMDZ and ORCHIDEE models
     2154    !                         ! Field exchange between LMDZ and NEMO models
     2155    ! level_coupling_esm = 3  ! Field exchange between LMDZ and ORCHIDEE models
     2156    !                         ! Field exchange between LMDZ and NEMO models
     2157    level_coupling_esm_omp=0 ! default value
     2158    CALL getin('level_coupling_esm',level_coupling_esm_omp)
     2159    ! << PC
    21502160
    21512161    !$OMP END MASTER
     
    24042414    carbon_cycle_tr = carbon_cycle_tr_omp
    24052415    carbon_cycle_cpl = carbon_cycle_cpl_omp
     2416    level_coupling_esm = level_coupling_esm_omp
    24062417
    24072418    ! Test of coherence between type_ocean and version_ocean
     
    25112522       WRITE(lunout,*)'ifl_pbltree is now changed to zero'
    25122523       ifl_pbltree=0
    2513     END IF
     2524    ENDIF
    25142525
    25152526    !$OMP MASTER
    25162527
    2517     write(lunout,*)' ##############################################'
    2518     write(lunout,*)' Configuration des parametres de la physique: '
    2519     write(lunout,*)' Type ocean = ', type_ocean
    2520     write(lunout,*)' Version ocean = ', version_ocean
    2521     write(lunout,*)' Config veget = ', ok_veget,type_veget
    2522     write(lunout,*)' Snow model SISVAT : ok_snow = ', ok_snow
    2523     write(lunout,*)' Config xml pour XIOS : ok_all_xml = ', ok_all_xml
    2524     write(lunout,*)' Sortie journaliere = ', ok_journe
    2525     write(lunout,*)' Sortie haute frequence = ', ok_hf
    2526     write(lunout,*)' Sortie mensuelle = ', ok_mensuel
    2527     write(lunout,*)' Sortie instantanee = ', ok_instan
    2528     write(lunout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
    2529     write(lunout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
    2530     write(lunout,*)' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
    2531     write(lunout,*)' Frequence appel simulateur AIRS, freq_AIRS =', freq_AIRS
    2532     write(lunout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
    2533     write(lunout,*)' Excentricite = ',R_ecc
    2534     write(lunout,*)' Equinoxe = ',R_peri
    2535     write(lunout,*)' Inclinaison =',R_incl
    2536     write(lunout,*)' Constante solaire =',solaire
    2537     write(lunout,*)' ok_suntime_rrtm =',ok_suntime_rrtm
    2538     write(lunout,*)' co2_ppm =',co2_ppm
    2539     write(lunout,*)' RCO2_act = ',RCO2_act
    2540     write(lunout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
    2541     write(lunout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
    2542     write(lunout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
    2543     write(lunout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
    2544     write(lunout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
    2545     write(lunout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
    2546     write(lunout,*)' RCFC12_per = ',RCFC12_per
    2547     write(lunout,*)' cvl_comp_threshold=', cvl_comp_threshold
    2548     write(lunout,*)' cvl_sig2feed=', cvl_sig2feed
    2549     write(lunout,*)' cvl_corr=', cvl_corr
    2550     write(lunout,*)'ok_lic_melt=', ok_lic_melt
    2551     write(lunout,*)'ok_lic_cond=', ok_lic_cond
    2552     write(lunout,*)'iflag_cycle_diurne=',iflag_cycle_diurne
    2553     write(lunout,*)'soil_model=',soil_model
    2554     write(lunout,*)'new_oliq=',new_oliq
    2555     write(lunout,*)'ok_orodr=',ok_orodr
    2556     write(lunout,*)'ok_orolf=',ok_orolf
    2557     write(lunout,*)'ok_limitvrai=',ok_limitvrai
    2558     write(lunout,*)'nbapp_rad=',nbapp_rad
    2559     write(lunout,*)'iflag_con=',iflag_con
    2560     write(lunout,*)'nbapp_cv=',nbapp_cv
    2561     write(lunout,*)'nbapp_wk=',nbapp_wk
    2562     write(lunout,*)'iflag_ener_conserv=',iflag_ener_conserv
    2563     write(lunout,*)'ok_conserv_q=',ok_conserv_q
    2564     write(lunout,*)'iflag_fisrtilp_qsat=',iflag_fisrtilp_qsat
    2565     write(lunout,*)'iflag_bergeron=',iflag_bergeron
    2566     write(lunout,*)' epmax = ', epmax
    2567     write(lunout,*)' coef_epmax_cape = ', coef_epmax_cape
    2568     write(lunout,*)' ok_adj_ema = ', ok_adj_ema
    2569     write(lunout,*)' iflag_clw = ', iflag_clw
    2570     write(lunout,*)' cld_lc_lsc = ', cld_lc_lsc
    2571     write(lunout,*)' cld_lc_con = ', cld_lc_con
    2572     write(lunout,*)' cld_tau_lsc = ', cld_tau_lsc
    2573     write(lunout,*)' cld_tau_con = ', cld_tau_con
    2574     write(lunout,*)' ffallv_lsc = ', ffallv_lsc
    2575     write(lunout,*)' ffallv_con = ', ffallv_con
    2576     write(lunout,*)' coef_eva = ', coef_eva
    2577     write(lunout,*)' reevap_ice = ', reevap_ice
    2578     write(lunout,*)' iflag_pdf = ', iflag_pdf
    2579     write(lunout,*)' iflag_cld_th = ', iflag_cld_th
    2580     write(lunout,*)' iflag_cld_cv = ', iflag_cld_cv
    2581     write(lunout,*)' tau_cld_cv = ', tau_cld_cv
    2582     write(lunout,*)' coefw_cld_cv = ', coefw_cld_cv
    2583     write(lunout,*)' iflag_radia = ', iflag_radia
    2584     write(lunout,*)' iflag_rrtm = ', iflag_rrtm
    2585     write(lunout,*)' NSW = ', NSW
    2586     write(lunout,*)' iflag_albedo = ', iflag_albedo !albedo SB
    2587     write(lunout,*)' ok_chlorophyll =',ok_chlorophyll ! albedo SB
    2588     write(lunout,*)' iflag_ratqs = ', iflag_ratqs
    2589     write(lunout,*)' seuil_inversion = ', seuil_inversion
    2590     write(lunout,*)' fact_cldcon = ', fact_cldcon
    2591     write(lunout,*)' facttemps = ', facttemps
    2592     write(lunout,*)' ok_newmicro = ',ok_newmicro
    2593     write(lunout,*)' ratqsbas = ',ratqsbas
    2594     write(lunout,*)' ratqshaut = ',ratqshaut
    2595     write(lunout,*)' tau_ratqs = ',tau_ratqs
    2596     write(lunout,*)' top_height = ',top_height
    2597     write(lunout,*)' rad_froid = ',rad_froid
    2598     write(lunout,*)' rad_chau1 = ',rad_chau1
    2599     write(lunout,*)' rad_chau2 = ',rad_chau2
    2600     write(lunout,*)' t_glace_min = ',t_glace_min
    2601     write(lunout,*)' t_glace_max = ',t_glace_max
    2602     write(lunout,*)' exposant_glace = ',exposant_glace
    2603     write(lunout,*)' iflag_t_glace = ',iflag_t_glace
    2604     write(lunout,*)' iflag_cloudth_vert = ',iflag_cloudth_vert
    2605     write(lunout,*)' iflag_rain_incloud_vol = ',iflag_rain_incloud_vol
    2606     write(lunout,*)' iflag_ice_thermo = ',iflag_ice_thermo
    2607     write(lunout,*)' rei_min = ',rei_min
    2608     write(lunout,*)' rei_max = ',rei_max
    2609     write(lunout,*)' overlap = ',overlap
    2610     write(lunout,*)' cdmmax = ',cdmmax
    2611     write(lunout,*)' cdhmax = ',cdhmax
    2612     write(lunout,*)' ksta = ',ksta
    2613     write(lunout,*)' ksta_ter = ',ksta_ter
    2614     write(lunout,*)' f_ri_cd_min = ',f_ri_cd_min
    2615     write(lunout,*)' ok_kzmin = ',ok_kzmin
    2616     write(lunout,*)' pbl_lmixmin_alpha = ',pbl_lmixmin_alpha
    2617     write(lunout,*)' fmagic = ',fmagic
    2618     write(lunout,*)' pmagic = ',pmagic
    2619     write(lunout,*)' ok_ade = ',ok_ade
    2620     write(lunout,*)' ok_aie = ',ok_aie
    2621     write(lunout,*)' ok_alw = ',ok_alw
    2622     write(lunout,*)' aerosol_couple = ', aerosol_couple
    2623     write(lunout,*)' chemistry_couple = ', chemistry_couple
    2624     write(lunout,*)' flag_aerosol = ', flag_aerosol
    2625     write(lunout,*)' flag_aerosol_strat= ', flag_aerosol_strat
    2626     write(lunout,*)' new_aod = ', new_aod
    2627     write(lunout,*)' aer_type = ',aer_type
    2628     write(lunout,*)' bl95_b0 = ',bl95_b0
    2629     write(lunout,*)' bl95_b1 = ',bl95_b1
    2630     write(lunout,*)' lev_histhf = ',lev_histhf
    2631     write(lunout,*)' lev_histday = ',lev_histday
    2632     write(lunout,*)' lev_histmth = ',lev_histmth
    2633     write(lunout,*)' lev_histins = ',lev_histins
    2634     write(lunout,*)' lev_histLES = ',lev_histLES
    2635     write(lunout,*)' lev_histdayNMC = ',lev_histdayNMC
    2636     write(lunout,*)' levout_histNMC = ',levout_histNMC
    2637     write(lunout,*)' ok_histNMC = ',ok_histNMC
    2638     write(lunout,*)' freq_outNMC = ',freq_outNMC
    2639     write(lunout,*)' freq_calNMC = ',freq_calNMC
    2640     write(lunout,*)' iflag_pbl = ', iflag_pbl
     2528    WRITE(lunout,*) ' ##############################################'
     2529    WRITE(lunout,*) ' Configuration des parametres de la physique: '
     2530    WRITE(lunout,*) ' Type ocean = ', type_ocean
     2531    WRITE(lunout,*) ' Version ocean = ', version_ocean
     2532    WRITE(lunout,*) ' Config veget = ', ok_veget,type_veget
     2533    WRITE(lunout,*) ' Snow model SISVAT : ok_snow = ', ok_snow
     2534    WRITE(lunout,*) ' Config xml pour XIOS : ok_all_xml = ', ok_all_xml
     2535    WRITE(lunout,*) ' Sortie journaliere = ', ok_journe
     2536    WRITE(lunout,*) ' Sortie haute frequence = ', ok_hf
     2537    WRITE(lunout,*) ' Sortie mensuelle = ', ok_mensuel
     2538    WRITE(lunout,*) ' Sortie instantanee = ', ok_instan
     2539    WRITE(lunout,*) ' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
     2540    WRITE(lunout,*) ' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
     2541    WRITE(lunout,*) ' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
     2542    WRITE(lunout,*) ' Frequence appel simulateur AIRS, freq_AIRS =', freq_AIRS
     2543    WRITE(lunout,*) ' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
     2544    WRITE(lunout,*) ' Excentricite = ',R_ecc
     2545    WRITE(lunout,*) ' Equinoxe = ',R_peri
     2546    WRITE(lunout,*) ' Inclinaison =',R_incl
     2547    WRITE(lunout,*) ' Constante solaire =',solaire
     2548    WRITE(lunout,*) ' ok_suntime_rrtm =',ok_suntime_rrtm
     2549    WRITE(lunout,*) ' co2_ppm =',co2_ppm
     2550    WRITE(lunout,*) ' RCO2_act = ',RCO2_act
     2551    WRITE(lunout,*) ' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
     2552    WRITE(lunout,*) ' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
     2553    WRITE(lunout,*) ' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
     2554    WRITE(lunout,*) ' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
     2555    WRITE(lunout,*) ' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
     2556    WRITE(lunout,*) ' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
     2557    WRITE(lunout,*) ' RCFC12_per = ',RCFC12_per
     2558    WRITE(lunout,*) ' cvl_comp_threshold=', cvl_comp_threshold
     2559    WRITE(lunout,*) ' cvl_sig2feed=', cvl_sig2feed
     2560    WRITE(lunout,*) ' cvl_corr=', cvl_corr
     2561    WRITE(lunout,*) ' ok_lic_melt=', ok_lic_melt
     2562    WRITE(lunout,*) ' ok_lic_cond=', ok_lic_cond
     2563    WRITE(lunout,*) ' iflag_cycle_diurne=',iflag_cycle_diurne
     2564    WRITE(lunout,*) ' soil_model=',soil_model
     2565    WRITE(lunout,*) ' new_oliq=',new_oliq
     2566    WRITE(lunout,*) ' ok_orodr=',ok_orodr
     2567    WRITE(lunout,*) ' ok_orolf=',ok_orolf
     2568    WRITE(lunout,*) ' ok_limitvrai=',ok_limitvrai
     2569    WRITE(lunout,*) ' nbapp_rad=',nbapp_rad
     2570    WRITE(lunout,*) ' iflag_con=',iflag_con
     2571    WRITE(lunout,*) ' nbapp_cv=',nbapp_cv
     2572    WRITE(lunout,*) ' nbapp_wk=',nbapp_wk
     2573    WRITE(lunout,*) ' iflag_ener_conserv=',iflag_ener_conserv
     2574    WRITE(lunout,*) ' ok_conserv_q=',ok_conserv_q
     2575    WRITE(lunout,*) ' iflag_fisrtilp_qsat=',iflag_fisrtilp_qsat
     2576    WRITE(lunout,*) ' iflag_bergeron=',iflag_bergeron
     2577    WRITE(lunout,*) ' epmax = ', epmax
     2578    WRITE(lunout,*) ' coef_epmax_cape = ', coef_epmax_cape
     2579    WRITE(lunout,*) ' ok_adj_ema = ', ok_adj_ema
     2580    WRITE(lunout,*) ' iflag_clw = ', iflag_clw
     2581    WRITE(lunout,*) ' cld_lc_lsc = ', cld_lc_lsc
     2582    WRITE(lunout,*) ' cld_lc_con = ', cld_lc_con
     2583    WRITE(lunout,*) ' cld_tau_lsc = ', cld_tau_lsc
     2584    WRITE(lunout,*) ' cld_tau_con = ', cld_tau_con
     2585    WRITE(lunout,*) ' ffallv_lsc = ', ffallv_lsc
     2586    WRITE(lunout,*) ' ffallv_con = ', ffallv_con
     2587    WRITE(lunout,*) ' coef_eva = ', coef_eva
     2588    WRITE(lunout,*) ' reevap_ice = ', reevap_ice
     2589    WRITE(lunout,*) ' iflag_pdf = ', iflag_pdf
     2590    WRITE(lunout,*) ' iflag_cld_th = ', iflag_cld_th
     2591    WRITE(lunout,*) ' iflag_cld_cv = ', iflag_cld_cv
     2592    WRITE(lunout,*) ' tau_cld_cv = ', tau_cld_cv
     2593    WRITE(lunout,*) ' coefw_cld_cv = ', coefw_cld_cv
     2594    WRITE(lunout,*) ' iflag_radia = ', iflag_radia
     2595    WRITE(lunout,*) ' iflag_rrtm = ', iflag_rrtm
     2596    WRITE(lunout,*) ' NSW = ', NSW
     2597    WRITE(lunout,*) ' iflag_albedo = ', iflag_albedo !albedo SB
     2598    WRITE(lunout,*) ' ok_chlorophyll =',ok_chlorophyll ! albedo SB
     2599    WRITE(lunout,*) ' iflag_ratqs = ', iflag_ratqs
     2600    WRITE(lunout,*) ' seuil_inversion = ', seuil_inversion
     2601    WRITE(lunout,*) ' fact_cldcon = ', fact_cldcon
     2602    WRITE(lunout,*) ' facttemps = ', facttemps
     2603    WRITE(lunout,*) ' ok_newmicro = ',ok_newmicro
     2604    WRITE(lunout,*) ' ratqsbas = ',ratqsbas
     2605    WRITE(lunout,*) ' ratqshaut = ',ratqshaut
     2606    WRITE(lunout,*) ' tau_ratqs = ',tau_ratqs
     2607    WRITE(lunout,*) ' top_height = ',top_height
     2608    WRITE(lunout,*) ' rad_froid = ',rad_froid
     2609    WRITE(lunout,*) ' rad_chau1 = ',rad_chau1
     2610    WRITE(lunout,*) ' rad_chau2 = ',rad_chau2
     2611    WRITE(lunout,*) ' t_glace_min = ',t_glace_min
     2612    WRITE(lunout,*) ' t_glace_max = ',t_glace_max
     2613    WRITE(lunout,*) ' exposant_glace = ',exposant_glace
     2614    WRITE(lunout,*) ' iflag_t_glace = ',iflag_t_glace
     2615    WRITE(lunout,*) ' iflag_cloudth_vert = ',iflag_cloudth_vert
     2616    WRITE(lunout,*) ' iflag_rain_incloud_vol = ',iflag_rain_incloud_vol
     2617    WRITE(lunout,*) ' iflag_ice_thermo = ',iflag_ice_thermo
     2618    WRITE(lunout,*) ' rei_min = ',rei_min
     2619    WRITE(lunout,*) ' rei_max = ',rei_max
     2620    WRITE(lunout,*) ' overlap = ',overlap
     2621    WRITE(lunout,*) ' cdmmax = ',cdmmax
     2622    WRITE(lunout,*) ' cdhmax = ',cdhmax
     2623    WRITE(lunout,*) ' ksta = ',ksta
     2624    WRITE(lunout,*) ' ksta_ter = ',ksta_ter
     2625    WRITE(lunout,*) ' f_ri_cd_min = ',f_ri_cd_min
     2626    WRITE(lunout,*) ' ok_kzmin = ',ok_kzmin
     2627    WRITE(lunout,*) ' pbl_lmixmin_alpha = ',pbl_lmixmin_alpha
     2628    WRITE(lunout,*) ' fmagic = ',fmagic
     2629    WRITE(lunout,*) ' pmagic = ',pmagic
     2630    WRITE(lunout,*) ' ok_ade = ',ok_ade
     2631    WRITE(lunout,*) ' ok_aie = ',ok_aie
     2632    WRITE(lunout,*) ' ok_alw = ',ok_alw
     2633    WRITE(lunout,*) ' aerosol_couple = ', aerosol_couple
     2634    WRITE(lunout,*) ' chemistry_couple = ', chemistry_couple
     2635    WRITE(lunout,*) ' flag_aerosol = ', flag_aerosol
     2636    WRITE(lunout,*) ' flag_aerosol_strat= ', flag_aerosol_strat
     2637    WRITE(lunout,*) ' new_aod = ', new_aod
     2638    WRITE(lunout,*) ' aer_type = ',aer_type
     2639    WRITE(lunout,*) ' bl95_b0 = ',bl95_b0
     2640    WRITE(lunout,*) ' bl95_b1 = ',bl95_b1
     2641    WRITE(lunout,*) ' lev_histhf = ',lev_histhf
     2642    WRITE(lunout,*) ' lev_histday = ',lev_histday
     2643    WRITE(lunout,*) ' lev_histmth = ',lev_histmth
     2644    WRITE(lunout,*) ' lev_histins = ',lev_histins
     2645    WRITE(lunout,*) ' lev_histLES = ',lev_histLES
     2646    WRITE(lunout,*) ' lev_histdayNMC = ',lev_histdayNMC
     2647    WRITE(lunout,*) ' levout_histNMC = ',levout_histNMC
     2648    WRITE(lunout,*) ' ok_histNMC = ',ok_histNMC
     2649    WRITE(lunout,*) ' freq_outNMC = ',freq_outNMC
     2650    WRITE(lunout,*) ' freq_calNMC = ',freq_calNMC
     2651    WRITE(lunout,*) ' iflag_pbl = ', iflag_pbl
    26412652!FC
    2642     write(lunout,*)' ifl_pbltree = ', ifl_pbltree
    2643     write(lunout,*)' Cd_frein = ', Cd_frein
    2644     write(lunout,*)' iflag_pbl_split = ', iflag_pbl_split
    2645     write(lunout,*)' iflag_order2_sollw = ', iflag_order2_sollw
    2646     write(lunout,*)' iflag_thermals = ', iflag_thermals
    2647     write(lunout,*)' iflag_thermals_ed = ', iflag_thermals_ed
    2648     write(lunout,*)' fact_thermals_ed_dz = ', fact_thermals_ed_dz
    2649     write(lunout,*)' iflag_thermals_optflux = ', iflag_thermals_optflux
    2650     write(lunout,*)' iflag_thermals_closure = ', iflag_thermals_closure
    2651     write(lunout,*)' iflag_clos = ', iflag_clos
    2652     write(lunout,*)' coef_clos_ls = ', coef_clos_ls
    2653     write(lunout,*)' type_run = ',type_run
    2654     write(lunout,*)' ok_cosp = ',ok_cosp
    2655     write(lunout,*)' ok_airs = ',ok_airs
    2656 
    2657     write(lunout,*)' ok_mensuelCOSP = ',ok_mensuelCOSP
    2658     write(lunout,*)' ok_journeCOSP = ',ok_journeCOSP
    2659     write(lunout,*)' ok_hfCOSP =',ok_hfCOSP
    2660     write(lunout,*)' solarlong0 = ', solarlong0
    2661     write(lunout,*)' qsol0 = ', qsol0
    2662     write(lunout,*)' evap0 = ', evap0
    2663     write(lunout,*)' albsno0 = ', albsno0
    2664     write(lunout,*)' iflag_sic = ', iflag_sic
    2665     write(lunout,*)' inertie_sol = ', inertie_sol
    2666     write(lunout,*)' inertie_sic = ', inertie_sic
    2667     write(lunout,*)' inertie_lic = ', inertie_lic
    2668     write(lunout,*)' inertie_sno = ', inertie_sno
    2669     write(lunout,*)' f_cdrag_ter = ',f_cdrag_ter
    2670     write(lunout,*)' f_cdrag_oce = ',f_cdrag_oce
    2671     write(lunout,*)' f_rugoro = ',f_rugoro
    2672     write(lunout,*)' z0min = ',z0min
    2673     write(lunout,*)' supcrit1 = ', supcrit1
    2674     write(lunout,*)' supcrit2 = ', supcrit2
    2675     write(lunout,*)' iflag_mix = ', iflag_mix
    2676     write(lunout,*)' iflag_mix_adiab = ', iflag_mix_adiab
    2677     write(lunout,*)' scut = ', scut
    2678     write(lunout,*)' qqa1 = ', qqa1
    2679     write(lunout,*)' qqa2 = ', qqa2
    2680     write(lunout,*)' gammas = ', gammas
    2681     write(lunout,*)' Fmax = ', Fmax
    2682     write(lunout,*)' tmax_fonte_cv = ', tmax_fonte_cv
    2683     write(lunout,*)' alphas = ', alphas
    2684     write(lunout,*)' iflag_wake = ', iflag_wake
    2685     write(lunout,*)' alp_offset = ', alp_offset
     2653    WRITE(lunout,*) ' ifl_pbltree = ', ifl_pbltree
     2654    WRITE(lunout,*) ' Cd_frein = ', Cd_frein
     2655    WRITE(lunout,*) ' iflag_pbl_split = ', iflag_pbl_split
     2656    WRITE(lunout,*) ' iflag_order2_sollw = ', iflag_order2_sollw
     2657    WRITE(lunout,*) ' iflag_thermals = ', iflag_thermals
     2658    WRITE(lunout,*) ' iflag_thermals_ed = ', iflag_thermals_ed
     2659    WRITE(lunout,*) ' fact_thermals_ed_dz = ', fact_thermals_ed_dz
     2660    WRITE(lunout,*) ' iflag_thermals_optflux = ', iflag_thermals_optflux
     2661    WRITE(lunout,*) ' iflag_thermals_closure = ', iflag_thermals_closure
     2662    WRITE(lunout,*) ' iflag_clos = ', iflag_clos
     2663    WRITE(lunout,*) ' coef_clos_ls = ', coef_clos_ls
     2664    WRITE(lunout,*) ' type_run = ',type_run
     2665    WRITE(lunout,*) ' ok_cosp = ',ok_cosp
     2666    WRITE(lunout,*) ' ok_airs = ',ok_airs
     2667
     2668    WRITE(lunout,*) ' ok_mensuelCOSP = ',ok_mensuelCOSP
     2669    WRITE(lunout,*) ' ok_journeCOSP = ',ok_journeCOSP
     2670    WRITE(lunout,*) ' ok_hfCOSP =',ok_hfCOSP
     2671    WRITE(lunout,*) ' solarlong0 = ', solarlong0
     2672    WRITE(lunout,*) ' qsol0 = ', qsol0
     2673    WRITE(lunout,*) ' evap0 = ', evap0
     2674    WRITE(lunout,*) ' albsno0 = ', albsno0
     2675    WRITE(lunout,*) ' iflag_sic = ', iflag_sic
     2676    WRITE(lunout,*) ' inertie_sol = ', inertie_sol
     2677    WRITE(lunout,*) ' inertie_sic = ', inertie_sic
     2678    WRITE(lunout,*) ' inertie_lic = ', inertie_lic
     2679    WRITE(lunout,*) ' inertie_sno = ', inertie_sno
     2680    WRITE(lunout,*) ' f_cdrag_ter = ',f_cdrag_ter
     2681    WRITE(lunout,*) ' f_cdrag_oce = ',f_cdrag_oce
     2682    WRITE(lunout,*) ' f_rugoro = ',f_rugoro
     2683    WRITE(lunout,*) ' z0min = ',z0min
     2684    WRITE(lunout,*) ' supcrit1 = ', supcrit1
     2685    WRITE(lunout,*) ' supcrit2 = ', supcrit2
     2686    WRITE(lunout,*) ' iflag_mix = ', iflag_mix
     2687    WRITE(lunout,*) ' iflag_mix_adiab = ', iflag_mix_adiab
     2688    WRITE(lunout,*) ' scut = ', scut
     2689    WRITE(lunout,*) ' qqa1 = ', qqa1
     2690    WRITE(lunout,*) ' qqa2 = ', qqa2
     2691    WRITE(lunout,*) ' gammas = ', gammas
     2692    WRITE(lunout,*) ' Fmax = ', Fmax
     2693    WRITE(lunout,*) ' tmax_fonte_cv = ', tmax_fonte_cv
     2694    WRITE(lunout,*) ' alphas = ', alphas
     2695    WRITE(lunout,*) ' iflag_wake = ', iflag_wake
     2696    WRITE(lunout,*) ' alp_offset = ', alp_offset
    26862697    ! nrlmd le 10/04/2012
    2687     write(lunout,*)' iflag_trig_bl = ', iflag_trig_bl
    2688     write(lunout,*)' s_trig = ', s_trig
    2689     write(lunout,*)' tau_trig_shallow = ', tau_trig_shallow
    2690     write(lunout,*)' tau_trig_deep = ', tau_trig_deep
    2691     write(lunout,*)' iflag_clos_bl = ', iflag_clos_bl
     2698    WRITE(lunout,*) ' iflag_trig_bl = ', iflag_trig_bl
     2699    WRITE(lunout,*) ' s_trig = ', s_trig
     2700    WRITE(lunout,*) ' tau_trig_shallow = ', tau_trig_shallow
     2701    WRITE(lunout,*) ' tau_trig_deep = ', tau_trig_deep
     2702    WRITE(lunout,*) ' iflag_clos_bl = ', iflag_clos_bl
    26922703    ! fin nrlmd le 10/04/2012
    26932704
    2694     write(lunout,*)' lonmin lonmax latmin latmax bilKP_ins =',&
     2705    WRITE(lunout,*) ' lonmin lonmax latmin latmax bilKP_ins =',&
    26952706         lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
    2696     write(lunout,*)' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
     2707    WRITE(lunout,*) ' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
    26972708         ecrit_hf, ecrit_ins, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP, ecrit_LES
    26982709
    2699     write(lunout,*) 'ok_strato = ', ok_strato
    2700     write(lunout,*) 'ok_hines = ',  ok_hines
    2701     write(lunout,*) 'ok_gwd_rando = ',  ok_gwd_rando
    2702     write(lunout,*) 'ok_qch4 = ',  ok_qch4
    2703     write(lunout,*) 'gwd_rando_ruwmax = ', gwd_rando_ruwmax
    2704     write(lunout,*) 'gwd_rando_sat = ', gwd_rando_sat
    2705     write(lunout,*) 'gwd_front_ruwmax = ', gwd_front_ruwmax
    2706     write(lunout,*) 'gwd_front_sat = ', gwd_front_sat
    2707     write(lunout,*) 'SSO gkdrag =',gkdrag
    2708     write(lunout,*) 'SSO grahilo=',grahilo
    2709     write(lunout,*) 'SSO grcrit=',grcrit
    2710     write(lunout,*) 'SSO gfrcrit=',gfrcrit
    2711     write(lunout,*) 'SSO gkwake=',gkwake
    2712     write(lunout,*) 'SSO gklift=',gklift
    2713     write(lunout,*) 'adjust_tropopause = ', adjust_tropopause
    2714     write(lunout,*) 'ok_daily_climoz = ',ok_daily_climoz
    2715     write(lunout,*) 'read_climoz = ', read_climoz
    2716     write(lunout,*) 'carbon_cycle_tr = ', carbon_cycle_tr
    2717     write(lunout,*) 'carbon_cycle_cpl = ', carbon_cycle_cpl
     2710    WRITE(lunout,*) ' ok_strato = ', ok_strato
     2711    WRITE(lunout,*) ' ok_hines = ',  ok_hines
     2712    WRITE(lunout,*) ' ok_gwd_rando = ',  ok_gwd_rando
     2713    WRITE(lunout,*) ' ok_qch4 = ',  ok_qch4
     2714    WRITE(lunout,*) ' gwd_rando_ruwmax = ', gwd_rando_ruwmax
     2715    WRITE(lunout,*) ' gwd_rando_sat = ', gwd_rando_sat
     2716    WRITE(lunout,*) ' gwd_front_ruwmax = ', gwd_front_ruwmax
     2717    WRITE(lunout,*) ' gwd_front_sat = ', gwd_front_sat
     2718    WRITE(lunout,*) ' SSO gkdrag =',gkdrag
     2719    WRITE(lunout,*) ' SSO grahilo=',grahilo
     2720    WRITE(lunout,*) ' SSO grcrit=',grcrit
     2721    WRITE(lunout,*) ' SSO gfrcrit=',gfrcrit
     2722    WRITE(lunout,*) ' SSO gkwake=',gkwake
     2723    WRITE(lunout,*) ' SSO gklift=',gklift
     2724    WRITE(lunout,*) ' adjust_tropopause = ', adjust_tropopause
     2725    WRITE(lunout,*) ' ok_daily_climoz = ',ok_daily_climoz
     2726    WRITE(lunout,*) ' read_climoz = ', read_climoz
     2727    WRITE(lunout,*) ' carbon_cycle_tr = ', carbon_cycle_tr
     2728    WRITE(lunout,*) ' carbon_cycle_cpl = ', carbon_cycle_cpl
     2729    WRITE(lunout,*) ' level_coupling_esm = ', level_coupling_esm
    27182730
    27192731    !$OMP END MASTER
     
    27362748  !
    27372749  ! tau_calv:    temps de relaxation pour la fonte des glaciers
    2738 
     2750  !
    27392751  REAL          :: tau_calv
    2740   REAL,SAVE     :: tau_calv_omp
    2741 
     2752  REAL, SAVE    :: tau_calv_omp
    27422753  !
    27432754  !Config Key  = tau_calv
     
    27512762  !$OMP END MASTER
    27522763  !$OMP BARRIER
    2753 
     2764  !
    27542765  tau_calv=tau_calv_omp
    2755 
     2766  !
    27562767  !$OMP MASTER
    2757   write(lunout,*)' ##############################################'
     2768  WRITE(lunout,*)' ##############################################'
    27582769  WRITE(lunout,*)' Configuration de l''interface atm/surfaces  : '
    27592770  WRITE(lunout,*)' tau_calv = ',tau_calv
    27602771  !$OMP END MASTER
    2761 
     2772  !
    27622773  RETURN
    27632774
Note: See TracChangeset for help on using the changeset viewer.