Ignore:
Timestamp:
Oct 3, 2023, 11:21:28 AM (15 months ago)
Author:
jbclement
Message:

Mars PCM:
In 1D, 'q' has been converted from dimension (:,:) to (1,:,:) and 'q2' is now got through the module 'turb_mod'. It allows more generalization and to match dimension in the subroutines.
JBC

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3066 r3067  
    55contains
    66
    7 SUBROUTINE init_testphys1d(pem1d,ngrid,nlayer,odpref,nq,q,time,psurf,u,v,temp,startfiles_1D,therestart1D,therestartfi, &
    8                            ndt,ptif,pks,dttestphys,zqsat,dq,dqdyn,day0,day,gru,grv,w,q2,play,plev,   &
    9                            latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
     7SUBROUTINE init_testphys1d(pem1d,ngrid,nlayer,odpref,nq,q,time,psurf,u,v,temp,startfiles_1D,therestart1D, &
     8                           therestartfi,ndt,ptif,pks,dttestphys,zqsat,dq,dqdyn,day0,day,gru,grv,w,        &
     9                           play,plev,latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
    1010
    1111use ioipsl_getincom,          only: getin ! To use 'getin'
     
    1313use time_phylmdz_mod,         only: daysec, day_step, ecritphy, iphysiq
    1414use planete_h,                only: year_day, periheli, aphelie, peri_day, obliquit, emin_turb, lmixmin
    15 use surfdat_h,                only: albedodat, z0_default, z0, emissiv, emisice, albedice, iceradius, dtemisice, &
     15use surfdat_h,                only: albedodat, z0_default, z0, emissiv, emisice, albedice, iceradius, dtemisice,      &
    1616                                    zmea, zstd, zsig, zgam, zthe, hmons, summit, base, phisfi, watercaptag, watercap, &
    1717                                    tsurf, emis, qsurf
     
    3737use mod_grid_phy_lmdz,        only: regular_lonlat
    3838use phys_state_var_init_mod,  only: phys_state_var_init
     39use turb_mod,                 only: q2
    3940! Mostly for XIOS outputs:
    4041use mod_const_mpi,            only: COMM_LMDZ
     
    4849! Arguments
    4950!=======================================================================
    50 integer,            intent(in) :: ngrid, nlayer
    51 real,               intent(in) :: odpref        ! DOD reference pressure (Pa)
    52 logical,            intent(in) :: pem1d         ! If initialization for the 1D PEM
     51integer, intent(in) :: ngrid, nlayer
     52real,    intent(in) :: odpref        ! DOD reference pressure (Pa)
     53logical, intent(in) :: pem1d         ! If initialization for the 1D PEM
    5354
    5455integer, intent(inout) :: nq
    5556
    56 real, dimension(:,:), allocatable, intent(out) :: q     ! tracer mixing ratio (e.g. kg/kg)
    57 real,                              intent(out) :: time  ! time (0<time<1; time=0.5 at noon)
    58 real,                              intent(out) :: psurf ! Surface pressure
    59 real, dimension(nlayer),           intent(out) :: u, v  ! zonal, meridional wind
    60 real, dimension(nlayer),           intent(out) :: temp  ! temperature at the middle of the layers
    61 logical,                           intent(out) :: startfiles_1D, therestart1D, therestartfi ! Use of starting files for 1D
    62 integer,                           intent(out) :: ndt
    63 real,                              intent(out) :: ptif, pks
    64 real,                              intent(out) :: dttestphys                   ! testphys1d timestep
    65 real, dimension(:),   allocatable, intent(out) :: zqsat                        ! useful for (atm_wat_profile=2)
    66 real, dimension(:,:), allocatable, intent(out) :: dq, dqdyn                    ! Physical and dynamical tandencies
    67 integer,                           intent(out) :: day0                         ! initial (sol ; =0 at Ls=0) and final date
    68 real,                              intent(out) :: day                          ! date during the run
    69 real,                              intent(out) :: gru, grv                     ! prescribed "geostrophic" background wind
    70 real, dimension(nlayer),           intent(out) :: w                            ! "Dummy wind" in 1D
    71 real, dimension(nlayer + 1),       intent(out) :: q2                           ! Turbulent Kinetic Energy
    72 real, dimension(nlayer),           intent(out) :: play                         ! Pressure at the middle of the layers (Pa)
    73 real, dimension(nlayer + 1),       intent(out) :: plev                         ! intermediate pressure levels (pa)
    74 real, dimension(1),                intent(out) :: latitude, longitude, cell_area
    75 real,                              intent(out) :: atm_wat_profile, atm_wat_tau ! Force atmospheric water profiles
     57real, dimension(:,:,:), allocatable, intent(out) :: q     ! tracer mixing ratio (e.g. kg/kg)
     58real,                                intent(out) :: time  ! time (0<time<1; time=0.5 at noon)
     59real,                                intent(out) :: psurf ! Surface pressure
     60real, dimension(nlayer),             intent(out) :: u, v  ! zonal, meridional wind
     61real, dimension(nlayer),             intent(out) :: temp  ! temperature at the middle of the layers
     62logical,                             intent(out) :: startfiles_1D, therestart1D, therestartfi ! Use of starting files for 1D
     63integer,                             intent(out) :: ndt
     64real,                                intent(out) :: ptif, pks
     65real,                                intent(out) :: dttestphys                   ! testphys1d timestep
     66real, dimension(:),     allocatable, intent(out) :: zqsat                        ! useful for (atm_wat_profile=2)
     67real, dimension(:,:,:), allocatable, intent(out) :: dq, dqdyn                    ! Physical and dynamical tandencies
     68integer,                             intent(out) :: day0                         ! initial (sol ; =0 at Ls=0) and final date
     69real,                                intent(out) :: day                          ! date during the run
     70real,                                intent(out) :: gru, grv                     ! prescribed "geostrophic" background wind
     71real, dimension(nlayer),             intent(out) :: w                            ! "Dummy wind" in 1D
     72real, dimension(nlayer),             intent(out) :: play                         ! Pressure at the middle of the layers (Pa)
     73real, dimension(nlayer + 1),         intent(out) :: plev                         ! intermediate pressure levels (pa)
     74real, dimension(1),                  intent(out) :: latitude, longitude, cell_area
     75real,                                intent(out) :: atm_wat_profile, atm_wat_tau ! Force atmospheric water profiles
    7676
    7777!=======================================================================
     
    237237
    238238! allocate arrays:
    239 allocate(tname(nq),q(nlayer,nq),zqsat(nlayer))
    240 allocate(dq(nlayer,nq),dqdyn(nlayer,nq),tnom_transp(nq))
     239allocate(tname(nq),q(1,nlayer,nq),zqsat(nlayer))
     240allocate(dq(1,nlayer,nq),dqdyn(1,nlayer,nq),tnom_transp(nq))
    241241
    242242! read tracer names from file traceur.def
     
    289289write(*,*) 'nqfils=',nqfils
    290290
    291 
    292 
    293291#ifdef CPP_XIOS
    294292    call init_physics_distribution(regular_lonlat,4,1,1,1,nlayer,COMM_LMDZ)
     
    455453    do iq = 1,nq
    456454        open(3,file = start1Dname,status = "old",action = "read")
    457         read(3,*) header, qsurf(1,iq,1),(q(ilayer,iq), ilayer = 1,nlayer)
     455        read(3,*) header, qsurf(1,iq,1),(q(1,ilayer,iq), ilayer = 1,nlayer)
    458456        if (trim(tname(iq)) /= trim(header)) then
    459457            write(*,*) 'Tracer names not compatible for initialization with "'//trim(start1Dname)//'"!'
     
    554552w = 0. ! default: no vertical wind
    555553
    556 ! Initialize turbulente kinetic energy
     554! Initialize turbulent kinetic energy
    557555q2 = 0.
    558556
     
    690688    ! q & psurf arrays are on the dynamics scalar grid
    691689    allocate(qdyn(2,1,llm,nq),psdyn(2,1))
    692     qdyn(1,1,1:llm,1:nq) = q(1:llm,1:nq)
     690    qdyn(1,1,1:llm,1:nq) = q(1,1:llm,1:nq)
    693691    psdyn(1:2,1) = psurf
    694692    call inichim_newstart(ngrid,nq,qdyn,qsurf(1,:,1),psdyn,flagh2o,flagthermo)
    695     q(1:llm,1:nq) = qdyn(1,1,1:llm,1:nq)
     693    q(1,1:llm,1:nq) = qdyn(1,1,1:llm,1:nq)
    696694endif
    697695
Note: See TracChangeset for help on using the changeset viewer.