Ignore:
Timestamp:
Jan 22, 2019, 4:21:59 PM (5 years ago)
Author:
Laurent Fairhead
Message:

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

File:
1 edited

Legend:

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

    r3379 r3435  
    343343!$OMP THREADPRIVATE(zxfluxlat_x, zxfluxlat_w)
    344344!jyg<
    345 !!! Entr\E9es suppl\E9mentaires couche-limite
     345!!! Entrees supplementaires couche-limite
    346346!!      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: t_x, t_w
    347347!!!$OMP THREADPRIVATE(t_x, t_w)
     
    349349!!!$OMP THREADPRIVATE(q_x, q_w)
    350350!>jyg
    351 ! Variables suppl\E9mentaires dans physiq.F relative au splitting de la surface
     351!!! Sorties ferret
     352      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: dtvdf_x, dtvdf_w
     353!$OMP THREADPRIVATE(dtvdf_x, dtvdf_w)
     354      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: dqvdf_x, dqvdf_w
     355!$OMP THREADPRIVATE(dqvdf_x, dqvdf_w)
     356! Variables supplementaires dans physiq.F relative au splitting de la surface
    352357      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: pbl_tke_input
    353358!$OMP THREADPRIVATE(pbl_tke_input)
     
    578583      ALLOCATE(plul_st(klon),plul_th(klon))
    579584      ALLOCATE(d_t_vdf(klon,klev),d_q_vdf(klon,klev),d_t_diss(klon,klev))
     585
     586      ALLOCATE(d_t_vdf_w(klon,klev),d_q_vdf_w(klon,klev))
     587      ALLOCATE(d_t_vdf_x(klon,klev),d_q_vdf_x(klon,klev))
     588
    580589      ALLOCATE(d_u_vdf(klon,klev),d_v_vdf(klon,klev))
    581590      ALLOCATE(d_t_oli(klon,klev),d_t_oro(klon,klev))
     
    589598! Special RRTM
    590599      ALLOCATE(ZLWFT0_i(klon,klev+1),ZSWFT0_i(klon,klev+1),ZFLDN0(klon,klev+1))
     600      ZFLDN0= 0.
    591601      ALLOCATE(ZFLUP0(klon,klev+1),ZFSDN0(klon,klev+1),ZFSUP0(klon,klev+1))
    592602!
     
    603613      ALLOCATE(dv_gwd_rando(klon,klev),dv_gwd_front(klon,klev))
    604614      ALLOCATE(east_gwstress(klon,klev),west_gwstress(klon,klev))
     615      east_gwstress(:,:)=0 !ym missing init
     616      west_gwstress(:,:)=0 !ym missing init
    605617      ALLOCATE(d_t_hin(klon,klev))
    606618      ALLOCATE(d_q_ch4(klon,klev))
     
    627639      ALLOCATE(od865aer(klon))
    628640      ALLOCATE(dryod550aer(klon))
     641      dryod550aer(:) = 0.
    629642      ALLOCATE(abs550aer(klon))
     643      abs550aer(:) = 0.
    630644      ALLOCATE(ec550aer(klon,klev))
    631645      ALLOCATE(od550lt1aer(klon))
     
    672686      ALLOCATE(toplwad0_aerop(klon), sollwad0_aerop(klon))
    673687
    674 ! FH Ajout de celles n??cessaires au phys_output_write_mod
     688! FH Ajout de celles necessaires au phys_output_write_mod
    675689
    676690      ALLOCATE(tal1(klon), pal1(klon), pab1(klon), pab2(klon))
     
    721735!!      ALLOCATE(q_x(klon,klev), q_w(klon,klev))
    722736!>jyg
    723       ALLOCATE(d_t_vdf_x(klon,klev), d_t_vdf_w(klon,klev))
    724       ALLOCATE(d_q_vdf_x(klon,klev), d_q_vdf_w(klon,klev))
     737      ALLOCATE(dtvdf_x(klon,klev), dtvdf_w(klon,klev))
     738      dtvdf_x = 0 ; dtvdf_w=0 ;   !ym missing init
     739      ALLOCATE(dqvdf_x(klon,klev), dqvdf_w(klon,klev))
     740      dqvdf_x = 0 ; dqvdf_w=0 ;   !ym missing init
    725741      ALLOCATE(pbl_tke_input(klon,klev+1,nbsrf))
    726742      ALLOCATE(t_therm(klon,klev), q_therm(klon,klev),u_therm(klon,klev), v_therm(klon,klev))
     
    738754      ALLOCATE(sens(klon), flwp(klon), fiwp(klon))
    739755      ALLOCATE(alp_bl_conv(klon), alp_bl_det(klon))
     756      ale_bl_stat(:)=0 ; alp_bl_conv(:)=0 ;  alp_bl_det(:)=0
    740757      ALLOCATE(alp_bl_fluct_m(klon), alp_bl_fluct_tke(klon))
     758      alp_bl_fluct_m(:)=0 ; alp_bl_fluct_tke(:)= 0.
    741759      ALLOCATE(alp_bl_stat(klon), n2(klon), s2(klon))
     760      alp_bl_stat(:)=0
    742761      ALLOCATE(proba_notrig(klon), random_notrig(klon))
    743762      ALLOCATE(cv_gen(klon))
     
    968987      DEALLOCATE(toplwad0_aerop, sollwad0_aerop)
    969988
    970 ! FH Ajout de celles n??cessaires au phys_output_write_mod
     989! FH Ajout de celles necessaires au phys_output_write_mod
    971990      DEALLOCATE(tal1, pal1, pab1, pab2)
    972991      DEALLOCATE(ptstar, pt0, slp)
Note: See TracChangeset for help on using the changeset viewer.