Changeset 2934 for LMDZ5


Ignore:
Timestamp:
Jul 7, 2017, 10:38:35 AM (7 years ago)
Author:
jghattas
Message:

Amelioration/correction pour retro-compatiblite avec different version de ORHCIDEE. Ajoute de test de coherence.

Location:
LMDZ5/branches/LMDZ_tree_FC/libf/phylmd
Files:
5 edited
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/LMDZ_tree_FC/libf/phylmd/conf_phys_m.F90

    r2925 r2934  
    24452445       CALL abort_physic('conf_phys', 'flag_bc_internal_mixture can only be activated with flag_aerosol=6',1)
    24462446    ENDIF
     2447
     2448    ! ORCHIDEE must be activated for ifl_pbltree=1
     2449    IF (.NOT. ok_veget .AND. ifl_pbltree==1) THEN
     2450       WRITE(lunout,*)' ORCHIDEE must be activated for ifl_pbltree=1'
     2451       CALL abort_physic('conf_phys','ok_veget and ifl_pbltree not coherent',1)
     2452    END IF
    24472453
    24482454    !$OMP MASTER
  • LMDZ5/branches/LMDZ_tree_FC/libf/phylmd/surf_land_mod.F90

    r2924 r2934  
    11!
    22MODULE surf_land_mod
    3 #ifndef LMDZ_nofrein
    43
    54  IMPLICIT NONE
     
    2221       flux_u1, flux_v1 , &
    2322       veget,lai,height)
    24 
    25 !FCveget,lai,height, &
    2623
    2724    USE dimphy
     
    5249    INCLUDE "dimsoil.h"
    5350    INCLUDE "YOMCST.h"
    54 !albedo SB >>>
    5551    INCLUDE "clesphys.h"
    56 !albedo SB <<<
    57 !FC
    58    INCLUDE "dimpft.h"
     52    INCLUDE "dimpft.h"
    5953
    6054
     
    107101    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l     
    108102    REAL, DIMENSION(klon), INTENT(OUT)       :: flux_u1, flux_v1  ! flux for U and V at first model level
    109 !FC
    110     REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT)       :: veget,lai
    111     REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT)            :: height
     103    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: veget,lai
     104    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: height
    112105
    113106! Local variables
     
    166159            emis_new, z0m, z0h, qsurf, &
    167160            veget, lai, height)       
    168 
    169 !    print*, " FC SORTIE surf_land_orchidee" ,height(1:100,2)
    170 !FC
    171161
    172162
     
    236226!****************************************************************************************
    237227
    238 #endif
    239228END MODULE surf_land_mod
    240229!
  • LMDZ5/branches/LMDZ_tree_FC/libf/phylmd/surf_land_orchidee_mod.F90

    r2927 r2934  
    44#ifndef ORCHIDEE_NOZ0H
    55#ifndef ORCHIDEE_NOFREIN
    6 !FC la derniere ligne et la fin
    76!
    87! This module controles the interface towards the model ORCHIDEE.
    98!
    109! Compatibility with ORCHIDIEE :
    11 ! The current version can be used with ORCHIDEE/trunk from revision 3525.
    12 ! This interface is used if none of the cpp keys ORCHIDEE_NOOPENMP or ORCHIDEE_NOZ0H is set.
     10! The current version can be used with ORCHIDEE/trunk from revision 4465.
     11! This interface is used if none of the cpp keys ORCHIDEE_NOOPENMP,
     12! ORCHIDEE_NOZ0H or ORCHIDEE_NOFREIN is set.
    1313!
    1414! Subroutines in this module : surf_land_orchidee
     
    4747       emis_new, z0m_new, z0h_new, qsurf, &
    4848       veget, lai, height )
    49 !FC
    5049
    5150
     
    113112!
    114113    INCLUDE "YOMCST.h"
    115 !FC
    116114    INCLUDE "dimpft.h"
    117115
     
    147145    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    148146    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0m_new, z0h_new
    149 !FC
    150     REAL, DIMENSION (klon,nvm_lmdz),INTENT(OUT)         :: veget
    151     REAL, DIMENSION (klon,nvm_lmdz),INTENT(OUT)         :: lai
    152     REAL, DIMENSION (klon,nvm_lmdz) ,INTENT(OUT)        :: height
     147    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: veget
     148    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: lai
     149    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: height
    153150
    154151
     
    230227! Test of coherence between variable ok_veget and cpp key CPP_VEGET
    231228#ifndef CPP_VEGET
    232              print* , "nvm_orch FC  ", nvm_orch
    233              print* , "nvm_lmdz FC  ", nvm_lmdz
    234 
    235229       abort_message='Pb de coherence: ok_veget = .true. mais CPP_VEGET = .false.'
    236230       CALL abort_physic(modname,abort_message,1)
     
    443437    IF (knon > 0) THEN
    444438#ifdef CPP_VEGET   
    445 !FC
    446            if(nvm_orch .ne.nvm_lmdz ) then
    447        abort_message='Pb de dimensiosn PFT: nvm_orch et nvm_lmdz differents.'
    448        CALL abort_physic(modname,abort_message,1)
    449            endif
    450 !FC
     439       IF (nvm_orch .NE. nvm_lmdz ) THEN
     440          abort_message='Pb de dimensiosn PFT: nvm_orch et nvm_lmdz differents.'
     441          CALL abort_physic(modname,abort_message,1)
     442       ENDIF
    451443
    452444       CALL intersurf_main_gathered (itime+itau_phy, nbp_lon, nbp_lat, knon, ktindex, dtime,  &
     
    460452            lon_scat, lat_scat, q2m, t2m, z0h_new(1:knon),&
    461453            veget(1:knon,:),lai(1:knon,:),height(1:knon,:),&
    462               coszang=yrmu0(1:knon))
     454            coszang=yrmu0(1:knon))
    463455#endif       
    464 !FC on doit mettre nvm_orch la ???
    465456    ENDIF
    466457
  • LMDZ5/branches/LMDZ_tree_FC/libf/phylmd/surf_land_orchidee_nofrein_mod.F90

    r2933 r2934  
    11!
    22MODULE surf_land_orchidee_mod
    3 #ifndef ORCHIDEE_NOOPENMP
    4 #ifndef ORCHIDEE_NOZ0H
    5 #ifndef ORCHIDEE_NOFREIN
    6 !FC la derniere ligne et la fin
     3#ifdef ORCHIDEE_NOFREIN
    74!
    85! This module controles the interface towards the model ORCHIDEE.
    96!
    107! Compatibility with ORCHIDIEE :
    11 ! The current version can be used with ORCHIDEE/trunk from revision 3525.
    12 ! This interface is used if none of the cpp keys ORCHIDEE_NOOPENMP or ORCHIDEE_NOZ0H is set.
     8! This module is compiled only if cpp key ORCHIDEE_NOFREIN is defined.
     9! The current version can be used with ORCHIDEE/trunk from revision 3525-4465
     10! (it can be used for later revisions also but it is not needed.)
     11!
    1312!
    1413! Subroutines in this module : surf_land_orchidee
     
    4746       emis_new, z0m_new, z0h_new, qsurf, &
    4847       veget, lai, height )
    49 !FC
    5048
    5149
     
    113111!
    114112    INCLUDE "YOMCST.h"
    115 !FC
    116113    INCLUDE "dimpft.h"
    117114
     
    147144    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    148145    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0m_new, z0h_new
    149 !FC
    150     REAL, DIMENSION (klon,nvm_lmdz),INTENT(OUT)         :: veget
    151     REAL, DIMENSION (klon,nvm_lmdz),INTENT(OUT)         :: lai
    152     REAL, DIMENSION (klon,nvm_lmdz) ,INTENT(OUT)        :: height
     146    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: veget ! dummy variables
     147    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: lai   ! dummy variables
     148    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: height! dummy variables
    153149
    154150
     
    225221    IF (check) WRITE(lunout,*)'Entree ', modname
    226222 
     223    IF (ifl_pbltree == 1) THEN
     224       abort_message='Pb de coherence: cette interface vers ORCHIDEE ne peut pas etre utilise avec ifl_pbltree'
     225       CALL abort_physic(modname,abort_message,1)
     226    END IF
     227
    227228! Initialisation
    228229 
     
    230231! Test of coherence between variable ok_veget and cpp key CPP_VEGET
    231232#ifndef CPP_VEGET
    232              print* , "nvm_orch FC  ", nvm_orch
    233              print* , "nvm_lmdz FC  ", nvm_lmdz
    234 
    235233       abort_message='Pb de coherence: ok_veget = .true. mais CPP_VEGET = .false.'
    236234       CALL abort_physic(modname,abort_message,1)
     
    426424               precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
    427425               evap, fluxsens, fluxlat, coastalflow, riverflow, &
    428                tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0m_new, &   
    429                lon_scat, lat_scat, q2m, t2m, z0h_new, nvm_orch)
     426               tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0m_new, &
     427               lon_scat, lat_scat, q2m, t2m, z0h_new)
    430428#endif         
    431429       ENDIF
     
    443441    IF (knon > 0) THEN
    444442#ifdef CPP_VEGET   
    445 !FC
    446            if(nvm_orch .ne.nvm_lmdz ) then
    447        abort_message='Pb de dimensiosn PFT: nvm_orch et nvm_lmdz differents.'
    448        CALL abort_physic(modname,abort_message,1)
    449            endif
    450 !FC
    451 
    452443       CALL intersurf_main_gathered (itime+itau_phy, nbp_lon, nbp_lat, knon, ktindex, dtime,  &
    453444            lrestart_read, lrestart_write, lalo, &
     
    458449            evap(1:knon), fluxsens(1:knon), fluxlat(1:knon), coastalflow(1:knon), riverflow(1:knon), &
    459450            tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0m_new(1:knon), &
    460             lon_scat, lat_scat, q2m, t2m, z0h_new(1:knon),&
    461             veget(1:knon,:),lai(1:knon,:),height(1:knon,:),&
    462               coszang=yrmu0(1:knon))
     451            lon_scat, lat_scat, q2m, t2m, z0h_new(1:knon), coszang=yrmu0(1:knon))
    463452#endif       
    464 !FC on doit mettre nvm_orch la ???
    465453    ENDIF
    466454
     
    691679#endif
    692680#endif
    693 #endif
    694681END MODULE surf_land_orchidee_mod
  • LMDZ5/branches/LMDZ_tree_FC/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r2925 r2934  
    4444       evap, fluxsens, fluxlat, &             
    4545       tsol_rad, tsurf_new, alb1_new, alb2_new, &
    46        emis_new, z0_new, z0h_new, qsurf)
     46       emis_new, z0_new, z0h_new, qsurf, &
     47       veget, lai, height)
    4748!   
    4849! Cette routine sert d'interface entre le modele atmospherique et le
     
    108109
    109110    INCLUDE "YOMCST.h"
    110  
     111    INCLUDE "dimpft.h" 
    111112!
    112113! Parametres d'entree
     
    138139    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    139140    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new, z0h_new
     141    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: veget ! dummy variables
     142    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: lai   ! dummy variables
     143    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: height! dummy variables
    140144
    141145! Local
  • LMDZ5/branches/LMDZ_tree_FC/libf/phylmd/surf_land_orchidee_noz0h_mod.F90

    r2925 r2934  
    4646       evap, fluxsens, fluxlat, &             
    4747       tsol_rad, tsurf_new, alb1_new, alb2_new, &
    48        emis_new, z0_new, z0h_new, qsurf)
     48       emis_new, z0_new, z0h_new, qsurf, &
     49       veget, lai, height)
    4950
    5051    USE mod_surf_para
     
    111112!
    112113    INCLUDE "YOMCST.h"
    113  
     114    INCLUDE "dimpft.h" 
    114115!
    115116! Parametres d'entree
     
    141142    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    142143    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new, z0h_new
     144    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: veget ! dummy variables
     145    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: lai   ! dummy variables
     146    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: height! dummy variables
    143147
    144148! Local
     
    213217
    214218    IF (check) WRITE(lunout,*)'Entree ', modname
     219
     220    IF (ifl_pbltree == 1) THEN
     221       abort_message='Pb de coherence: cette interface vers ORCHIDEE ne peut pas etre utilise avec ifl_pbltree'
     222       CALL abort_physic(modname,abort_message,1)
     223    END IF
    215224 
    216225! Initialisation
Note: See TracChangeset for help on using the changeset viewer.