Changeset 2571


Ignore:
Timestamp:
Jun 14, 2016, 1:51:43 PM (8 years ago)
Author:
jghattas
Message:

Interface LMDZ/ORCHIDEE :

  • copied previous default module surf_land_orchidee_mod.f90 into surf_land_orchidee_noz0h.f90. This interface can still be compiled if adding cpp key ORCHIDEE_NOZ0H
  • modified default interface by adding z0h as output from ORCHIDEE.
  • added comments in each module surf_land_orchidee_xxx of compatiblity with ORCHIDEE.
  • all modules surf_land_orchidee_xxx now send back z0h and z0m to surf_land_mod. But note that z0m and zOh are different only in the new default version surf_land_orchidee_mod.f90. In the old interfaces, z0h is a copy of z0m.


cosp : some small changes to be able to compile with gfortran

Location:
LMDZ5/trunk/libf/phylmd
Files:
6 edited
1 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/cosp/cosp_constants.F90

    r2428 r2571  
    108108                   -31.5,-28.5,-25.5,-22.5,-19.5,-16.5,-13.5,-10.5, -7.5, -4.5, &
    109109                    -1.5,  1.5,  4.5,  7.5, 10.5, 13.5, 16.5, 19.5, 22.5, 25.5/)
    110     real,parameter,dimension(2,LIDAR_NTEMP) :: LIDAR_PHASE_TEMP_BNDS=reshape(source=(/-273.15,-90.,-90.,-87.,-87.,-84.,-84.,-81.,-81.,-78., &
     110    real,parameter,dimension(2,LIDAR_NTEMP) :: LIDAR_PHASE_TEMP_BNDS=reshape(source=&
     111                    (/-273.15,-90.,-90.,-87.,-87.,-84.,-84.,-81.,-81.,-78., &
    111112                   -78.,-75.,-75.,-72.,-72.,-69.,-69.,-66.,-66.,-63., &
    112113                   -63.,-60.,-60.,-57.,-57.,-54.,-54.,-51.,-51.,-48., &
  • LMDZ5/trunk/libf/phylmd/cosp/cosp_output_mod.F90

    r2447 r2571  
    228228  real,dimension(2,SR_BINS) :: sratio_bounds
    229229  real,dimension(SR_BINS)   ::  sratio_ax
    230   CHARACTER(LEN=20), DIMENSION(3)  :: chfreq = (/ '1day', '1d', '3h' /)           
     230  CHARACTER(LEN=20), DIMENSION(3)  :: chfreq = (/ '1day', '1d  ', '3h  ' /)           
    231231
    232232!!! Variables d'entree
     
    363363      CALL histvert(cosp_nidfiles(iff),"column","column","count",Ncolumns,column_ax(1:Ncolumns),nvertcol(iff))
    364364
    365       CALL histvert(cosp_nidfiles(iff),"temp","temperature","C",LIDAR_NTEMP,LIDAR_PHASE_TEMP,nverttemp(iff))                                       
    366       CALL histvert(cosp_nidfiles(iff),"cth16","altitude","m",MISR_N_CTH,MISR_CTH,nvertmisr(iff))                                                                                                 
     365      CALL histvert(cosp_nidfiles(iff),"temp","temperature","C",LIDAR_NTEMP,LIDAR_PHASE_TEMP,nverttemp(iff))
     366
     367      CALL histvert(cosp_nidfiles(iff),"cth16","altitude","m",MISR_N_CTH,MISR_CTH,nvertmisr(iff))
     368
    367369!      CALL histvert(cosp_nidfiles(iff),"dbze","equivalent_reflectivity_factor","dBZ",DBZE_BINS,dbze_ax,nvertbze(iff))
    368370     
  • LMDZ5/trunk/libf/phylmd/cosp/phys_cosp.F90

    r2428 r2571  
    7373
    7474!! AI rajouter
    75   #include "cosp_defs.h"
     75#include "cosp_defs.h"
    7676  USE MOD_COSP_CONSTANTS
    7777  USE MOD_COSP_TYPES
  • LMDZ5/trunk/libf/phylmd/surf_land_mod.F90

    r2410 r2571  
    2424    USE surface_data, ONLY    : ok_veget
    2525
     26    ! See comments in each module surf_land_orchidee_xxx for compatiblity with ORCHIDEE
    2627#ifdef ORCHIDEE_NOOPENMP
     28    ! Compilation with cpp key ORCHIDEE NOOPENMP
    2729    USE surf_land_orchidee_noopenmp_mod
    2830#else
     31#if ORCHIDEE_NOZ0H
     32    ! Compilation with cpp key ORCHIDEE NOZ0H
     33    USE surf_land_orchidee_noz0h_mod
     34#else
     35    ! Compilation with default interface
    2936    USE surf_land_orchidee_mod
    3037#endif
     38#endif
     39
    3140    USE surf_land_bucket_mod
    3241    USE calcul_fluxs_mod
     
    141150            evap, fluxsens, fluxlat, &             
    142151            tsol_rad, tsurf_new, alb1_new, alb2_new, &
    143             emis_new, z0m, qsurf)       
    144         z0h(1:knon)=z0m(1:knon) ! En attendant mieux
     152            emis_new, z0m, z0h, qsurf)       
    145153
    146154
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_mod.F90

    r2410 r2571  
    22MODULE surf_land_orchidee_mod
    33#ifndef ORCHIDEE_NOOPENMP
     4#ifndef ORCHIDEE_NOZ0H
    45!
    56! This module controles the interface towards the model ORCHIDEE.
    67!
    78! Compatibility with ORCHIDIEE :
    8 ! The current version can be used with ORCHIDEE/trunk from revision 2961.
    9 ! This interface can also be used with ORCHIDEE/trunk revision 1078-2960 if changing
    10 ! coszang=yrmu0 into sinang=yrmu0 at 2 places later below in this module.
     9! The current version can be used with ORCHIDEE/trunk from revision 3525.
     10! This interface is used if none of the cpp keys ORCHIDEE_NOOPENMP or ORCHIDEE_NOZ0H is set.
    1111!
    1212! Subroutines in this module : surf_land_orchidee
     
    4444       evap, fluxsens, fluxlat, &             
    4545       tsol_rad, tsurf_new, alb1_new, alb2_new, &
    46        emis_new, z0_new, qsurf)
     46       emis_new, z0m_new, z0h_new, qsurf)
    4747
    4848    USE mod_surf_para
     
    104104!   alb2_new     albedo in near IR interval
    105105!   emis_new     emissivite
    106 !   z0_new       surface roughness
     106!   z0m_new      surface roughness for momentum
     107!   z0h_new      surface roughness for heat
    107108!   qsurf        air moisture at surface
    108109!
     
    137138    REAL, DIMENSION(klon), INTENT(OUT)        :: tsol_rad, tsurf_new
    138139    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    139     REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new
     140    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0m_new, z0h_new
    140141
    141142! Local
     
    403404
    404405#ifdef CPP_VEGET
    405           CALL intersurf_main (itime+itau_phy-1, nbp_lon, nbp_lat, knon, ktindex, dtime, &
    406                lrestart_read, lrestart_write, lalo, &
    407                contfrac, neighbours, resolution, date0, &
    408                zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
     406         CALL intersurf_initialize_gathered (itime+itau_phy-1, nbp_lon, nbp_lat, knon, ktindex, dtime, &
     407               lrestart_read, lrestart_write, lalo, contfrac, neighbours, resolution, date0, &
     408               zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, &
    409409               cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
    410410               precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
    411411               evap, fluxsens, fluxlat, coastalflow, riverflow, &
    412                tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
    413                lon_scat, lat_scat, q2m, t2m, coszang=yrmu0)
     412               tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0m_new, &
     413               lon_scat, lat_scat, q2m, t2m, z0h_new)
    414414#endif         
    415415       ENDIF
     
    427427    IF (knon > 0) THEN
    428428#ifdef CPP_VEGET   
    429        CALL intersurf_main (itime+itau_phy, nbp_lon, nbp_lat, knon, ktindex, dtime,  &
     429       CALL intersurf_main_gathered (itime+itau_phy, nbp_lon, nbp_lat, knon, ktindex, dtime,  &
    430430            lrestart_read, lrestart_write, lalo, &
    431431            contfrac, neighbours, resolution, date0, &
     
    434434            precip_rain(1:knon), precip_snow(1:knon), lwdown(1:knon), swnet(1:knon), swdown_vrai(1:knon), ps(1:knon), &
    435435            evap(1:knon), fluxsens(1:knon), fluxlat(1:knon), coastalflow(1:knon), riverflow(1:knon), &
    436             tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0_new(1:knon), &
    437             lon_scat, lat_scat, q2m, t2m, coszang=yrmu0(1:knon))
     436            tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0m_new(1:knon), &
     437            lon_scat, lat_scat, q2m, t2m, z0h_new(1:knon), coszang=yrmu0(1:knon))
    438438#endif       
    439439    ENDIF
     
    664664!
    665665#endif
     666#endif
    666667END MODULE surf_land_orchidee_mod
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_noopenmp_mod.F90

    r2410 r2571  
    4444       evap, fluxsens, fluxlat, &             
    4545       tsol_rad, tsurf_new, alb1_new, alb2_new, &
    46        emis_new, z0_new, qsurf)
     46       emis_new, z0_new, z0h_new, qsurf)
    4747!   
    4848! Cette routine sert d'interface entre le modele atmospherique et le
     
    9595!   emis_new     emissivite
    9696!   z0_new       surface roughness
     97!   z0h_new      surface roughness, it is the same as z0_new
    9798!   qsurf        air moisture at surface
    9899!
     
    136137    REAL, DIMENSION(klon), INTENT(OUT)        :: tsol_rad, tsurf_new
    137138    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    138     REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new
     139    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new, z0h_new
    139140
    140141! Local
     
    496497
    497498    albedo_keep(1:knon) = (albedo_out(1:knon,1)+albedo_out(1:knon,2))/2.
     499   
     500    ! ORCHIDEE only gives one value for z0_new. Copy it into z0h_new.
     501    z0h_new(:)=z0_new(:)
    498502
    499503!* Send to coupler
  • LMDZ5/trunk/libf/phylmd/surf_land_orchidee_noz0h_mod.F90

    r2570 r2571  
    11!
    2 MODULE surf_land_orchidee_mod
    3 #ifndef ORCHIDEE_NOOPENMP
     2MODULE surf_land_orchidee_noz0h_mod
     3#ifdef ORCHIDEE_NOZ0H
    44!
    55! This module controles the interface towards the model ORCHIDEE.
    66!
    77! Compatibility with ORCHIDIEE :
    8 ! The current version can be used with ORCHIDEE/trunk from revision 2961.
     8! This module is compiled only if CPP key ORCHIDEE_NOZ0H is defined.
     9! This version can be used with ORCHIDEE/trunk revision 2961-3525.
     10! It is possible to use this interface with later versions of ORCHIDEE/trunk than 3525 but
     11! in that case the option ROUGH_DYN=y in ORCHIDEE should not be set.
    912! This interface can also be used with ORCHIDEE/trunk revision 1078-2960 if changing
    1013! coszang=yrmu0 into sinang=yrmu0 at 2 places later below in this module.
     
    4447       evap, fluxsens, fluxlat, &             
    4548       tsol_rad, tsurf_new, alb1_new, alb2_new, &
    46        emis_new, z0_new, qsurf)
     49       emis_new, z0_new, z0h_new, qsurf)
    4750
    4851    USE mod_surf_para
     
    105108!   emis_new     emissivite
    106109!   z0_new       surface roughness
     110!   z0h_new      surface roughness, it is a copy from z0_new
    107111!   qsurf        air moisture at surface
    108112!
     
    137141    REAL, DIMENSION(klon), INTENT(OUT)        :: tsol_rad, tsurf_new
    138142    REAL, DIMENSION(klon), INTENT(OUT)        :: alb1_new, alb2_new
    139     REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new
     143    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new, z0h_new
    140144
    141145! Local
     
    438442#endif       
    439443    ENDIF
     444    z0h_new(:)=z0_new(:)
    440445
    441446    CALL Synchro_omp
     
    664669!
    665670#endif
    666 END MODULE surf_land_orchidee_mod
     671END MODULE surf_land_orchidee_noz0h_mod
Note: See TracChangeset for help on using the changeset viewer.