Ignore:
Timestamp:
Nov 17, 2023, 2:38:58 PM (14 months ago)
Author:
jbclement
Message:

Mars PCM/PEM:
Cleaning of the 1D initialization: any reference of the PEM has been removed from "init_testphys1D_mod.F90". This way is much cleaner even though it needs more code.
JBC

File:
1 edited

Legend:

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

    r3117 r3129  
    55contains
    66
    7 SUBROUTINE 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,        &
     7SUBROUTINE init_testphys1d(start1Dname,startfiname,startfiles_1D,therestart1D,therestartfi,ngrid,nlayer,odpref, &
     8                           nq,q,time,psurf,u,v,temp,ndt,ptif,pks,dttestphys,zqsat,dq,dqdyn,day0,day,gru,grv,w,  &
    99                           play,plev,latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
    1010
     
    3838use phys_state_var_init_mod,  only: phys_state_var_init
    3939use turb_mod,                 only: q2
    40 use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd
    41 use conf_phys_mod, only: conf_phys
     40use nonoro_gwd_ran_mod,       only: du_nonoro_gwd, dv_nonoro_gwd
     41use conf_phys_mod,            only: conf_phys
    4242! Mostly for XIOS outputs:
    4343use mod_const_mpi,            only: COMM_LMDZ
     
    5151! Arguments
    5252!=======================================================================
    53 integer, intent(in) :: ngrid, nlayer
    54 real,    intent(in) :: odpref        ! DOD reference pressure (Pa)
    55 logical, intent(in) :: pem1d         ! If initialization for the 1D PEM
     53integer,      intent(in) :: ngrid, nlayer
     54real,         intent(in) :: odpref                                    ! DOD reference pressure (Pa)
     55character(*), intent(in) :: start1Dname, startfiname                  ! Name of starting files for 1D
     56logical,      intent(in) :: startfiles_1D, therestart1D, therestartfi ! Use of starting files for 1D
    5657
    5758integer, intent(inout) :: nq
     
    6263real, dimension(nlayer),             intent(out) :: u, v  ! zonal, meridional wind
    6364real, dimension(nlayer),             intent(out) :: temp  ! temperature at the middle of the layers
    64 logical,                             intent(out) :: startfiles_1D, therestart1D, therestartfi ! Use of starting files for 1D
    6565integer,                             intent(out) :: ndt
    6666real,                                intent(out) :: ptif, pks
     
    9191! RV & JBC: Use of starting files for 1D
    9292logical                :: found
    93 character(len = 30)    :: header
     93character(30)          :: header
    9494real, dimension(100)   :: tab_cntrl
    9595real, dimension(1,2,1) :: albedo_read ! surface albedo
     
    100100
    101101! MVals: isotopes as in the dynamics (CRisi)
    102 integer                                        :: ifils, ipere, generation, ierr0
    103 character(len = 30), dimension(:), allocatable :: tnom_transp ! transporting fluid short name
    104 character(len = 80)                            :: line        ! to store a line of text
    105 logical                                        :: continu, there
     102integer                                  :: ifils, ipere, generation, ierr0
     103character(30), dimension(:), allocatable :: tnom_transp ! transporting fluid short name
     104character(80)                            :: line        ! to store a line of text
     105logical                                  :: continu
    106106
    107107! LL: Possibility to add subsurface ice
     
    113113real :: flux_geo_tmp
    114114
    115 ! JBC: To initialize the 1D PEM
    116 character(:), allocatable :: start1Dname, startfiname ! Name of starting files for 1D
    117 
    118115!=======================================================================
    119116! Code
    120117!=======================================================================
    121 if (.not. pem1d) then
    122     start1Dname = 'start1D.txt'
    123     startfiname = 'startfi.nc'
    124     startfiles_1D = .false.
    125     !------------------------------------------------------
    126     ! Loading run parameters from "run.def" file
    127     !------------------------------------------------------
    128     ! check if 'run.def' file is around. Otherwise reading parameters
    129     ! from callphys.def via getin() routine won't work.
    130     inquire(file = 'run.def',exist = there)
    131     if (.not. there) then
    132         write(*,*) 'Cannot find required file "run.def"'
    133         write(*,*) '  (which should contain some input parameters along with the following line: INCLUDEDEF=callphys.def)'
    134         write(*,*) ' ... might as well stop here ...'
    135         error stop
    136     endif
    137 
    138     write(*,*)'Do you want to use starting files and/or to write restarting files?'
    139     call getin("startfiles_1D",startfiles_1D)
    140     write(*,*) " startfiles_1D = ", startfiles_1D
    141 else
    142     start1dname = 'start1D_evol.txt'
    143     startfiname = 'startfi_evol.nc'
    144     startfiles_1D = .true.
    145 endif
    146 
    147 therestart1D = .false.
    148 therestartfi = .false.
    149 inquire(file = start1Dname,exist = therestart1D)
    150 if (startfiles_1D .and. .not. therestart1D) then
    151     write(*,*) 'There is no "'//start1Dname//'" file!'
    152     if (.not. pem1d) then
    153         write(*,*) 'Initialization is done with default values.'
    154     else
    155         error stop 'Initialization cannot be done for the 1D PEM.'
    156     endif
    157 endif
    158 inquire(file = startfiname,exist = therestartfi)
    159 if (.not. therestartfi) then
    160     write(*,*) 'There is no "'//startfiname//'" file!'
    161     if (.not. pem1d) then
    162         write(*,*) 'Initialization is done with default values.'
    163     else
    164         error stop 'Initialization cannot be done for the 1D PEM.'
    165     endif
    166 endif
    167 
    168118!------------------------------------------------------
    169119! Prescribed constants to be set here
     
    309259    time = time/24. ! convert time (hours) to fraction of sol
    310260else
    311     call open_startphy(startfiname)
     261    call open_startphy(trim(startfiname))
    312262    call get_var("controle",tab_cntrl,found)
    313263    if (.not. found) then
     
    351301    call getin("psurf",psurf)
    352302else
    353     open(3,file = start1Dname,status = "old",action = "read")
     303    open(3,file = trim(start1Dname),status = "old",action = "read")
    354304    read(3,*) header, psurf
    355305endif
     
    683633    ! check if "h2o_vap" has already been initialized
    684634    ! (it has been if there is a "profile_h2o_vap" file around)
    685     inquire(file = "profile_h2o_vap",exist = there)
    686     if (there) then
     635    inquire(file = "profile_h2o_vap",exist = found)
     636    if (found) then
    687637        flagh2o = 0 ! 0: do not initialize h2o_vap
    688638    else
Note: See TracChangeset for help on using the changeset viewer.