MODULE init_testphys1d_mod implicit none contains SUBROUTINE init_testphys1d(ngrid,nq,nlayer,odpref,ndt,ptif,pks,dttestphys,startfiles_1D,q,zqsat,qsurf,dq,dqdyn, & day0,day,time,psurf,tsurf,gru,grv,u,v,w,q2,play,plev,tsoil,temp,albedo,emis, & latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau) use ioipsl_getincom, only: getin ! To use 'getin' use comcstfi_h, only: pi, rad, omeg, g, mugaz, rcp, r, cpp use time_phylmdz_mod, only: daysec, day_step, ecritphy, iphysiq use planete_h, only: year_day, periheli, aphelie, peri_day, obliquit, emin_turb, lmixmin use surfdat_h, only: albedodat, z0_default, z0, emissiv, emisice, albedice, iceradius, dtemisice, & zmea, zstd, zsig, zgam, zthe, hmons, summit, base, phisfi, watercaptag, watercap use infotrac, only: nqtot, tname, nqperes, nqfils use read_profile_mod, only: read_profile use iostart, only: open_startphy, get_var, close_startphy use physics_distribution_mod, only: init_physics_distribution use comsoil_h, only: volcapa, nsoilmx, inertiesoil, inertiedat, layer, mlayer, flux_geo use comvert_mod, only: ap, bp, aps, bps, pa, preff, presnivs, pseudoalt, scaleheight use dimradmars_mod, only: tauvis, totcloudfrac use regular_lonlat_mod, only: init_regular_lonlat use mod_interface_dyn_phys, only: init_interface_dyn_phys use geometry_mod, only: init_geometry use dimphy, only: init_dimphy use comgeomfi_h, only: sinlat, ini_fillgeom use slope_mod, only: theta_sl, psi_sl use comslope_mod, only: def_slope, subslope_dist use dust_param_mod, only: tauscaling use tracer_mod, only: igcm_co2 use logic_mod, only: hybrid use vertical_layers_mod, only: init_vertical_layers use inichim_newstart_mod, only: inichim_newstart use mod_grid_phy_lmdz, only: regular_lonlat use phys_state_var_init_mod, only: phys_state_var_init ! Mostly for XIOS outputs: use mod_const_mpi, only: COMM_LMDZ implicit none include "dimensions.h" include "callkeys.h" !======================================================================= ! Arguments !======================================================================= integer, intent(in) :: ngrid, nlayer real, intent(in) :: odpref ! DOD reference pressure (Pa) integer, intent(inout) :: nq integer, intent(out) :: ndt real, intent(out) :: ptif, pks real, intent(out) :: dttestphys ! testphys1d timestep logical, intent(out) :: startfiles_1D ! Use of "start1D.txt" and "startfi.nc" files real, dimension(:,:), allocatable, intent(out) :: q ! tracer mixing ratio (e.g. kg/kg) real, dimension(:), allocatable, intent(out) :: zqsat ! useful for (atm_wat_profile=2) real, dimension(:), allocatable, intent(out) :: qsurf ! tracer surface budget (e.g. kg.m-2) real, dimension(:,:), allocatable, intent(out) :: dq, dqdyn ! Physical and dynamical tandencies integer, intent(out) :: day0 ! initial (sol ; =0 at Ls=0) and final date real, intent(out) :: day ! date during the run real, intent(out) :: time ! time (0=1!" stop endif endif ! allocate arrays: allocate(tname(nq),q(nlayer,nq),zqsat(nlayer),qsurf(nq)) allocate(dq(nlayer,nq),dqdyn(nlayer,nq),tnom_transp(nq)) ! read tracer names from file traceur.def do iq = 1,nq read(90,'(80a)',iostat = ierr) line ! store the line from traceur.def if (ierr /= 0) then write(*,*) 'testphys1d: error reading tracer names...' stop endif ! if format is tnom_0, tnom_transp (isotopes) read(line,*,iostat = ierr0) tname(iq),tnom_transp(iq) if (ierr0 /= 0) then read(line,*) tname(iq) tnom_transp(iq) = 'air' endif enddo close(90) ! Isotopes: as in the 3D case we have to determine father/son relations for isotopes and carrying fluid allocate(nqfils(nqtot)) nqperes = 0 nqfils(:) = 0 do iq = 1,nqtot if (tnom_transp(iq) == 'air') then ! ceci est un traceur père write(*,*) 'Le traceur',iq,', appele ',trim(tname(iq)),', est un pere' nqperes = nqperes + 1 else !if (tnom_transp(iq) == 'air') then ! ceci est un fils. Qui est son père? write(*,*) 'Le traceur',iq,', appele ',trim(tname(iq)),', est un fils' continu = .true. ipere = 1 do while (continu) if (tnom_transp(iq) == tname(ipere)) then ! Son père est ipere write(*,*) 'Le traceur',iq,'appele ',trim(tname(iq)),' est le fils de ',ipere,'appele ',trim(tname(ipere)) nqfils(ipere) = nqfils(ipere) + 1 continu = .false. else !if (tnom_transp(iq) == tnom_0(ipere)) then ipere = ipere + 1 if (ipere > nqtot) then write(*,*) 'Le traceur',iq,'appele ',trim(tname(iq)),', est orpelin.' call abort_gcm('infotrac_init','Un traceur est orphelin',1) endif !if (ipere > nqtot) then endif !if (tnom_transp(iq) == tnom_0(ipere)) then enddo !do while (continu) endif !if (tnom_transp(iq) == 'air') then enddo !do iq=1,nqtot write(*,*) 'nqperes=',nqperes write(*,*) 'nqfils=',nqfils ! Initialize tracers here: write(*,*) "testphys1d: initializing tracers" if (.not. therestart1D) then call read_profile(nq,nlayer,qsurf,q) else do iq = 1,nq open(3,file = 'start1D.txt',status = "old",action = "read") read(3,*) header, qsurf(iq),(q(ilayer,iq), ilayer = 1,nlayer) if (trim(tname(iq)) /= trim(header)) then write(*,*) 'Tracer names not compatible for initialization with "start1D.txt"!' stop endif enddo endif call init_physics_distribution(regular_lonlat,4,1,1,1,nlayer,COMM_LMDZ) ! Date and local time at beginning of run ! --------------------------------------- if (.not. startfiles_1D) then ! Date (in sols since spring solstice) at beginning of run day0 = 0 ! default value for day0 write(*,*) 'Initial date (in martian sols ; =0 at Ls=0)?' call getin("day0",day0) day = float(day0) write(*,*) " day0 = ",day0 ! Local time at beginning of run time = 0 ! default value for time write(*,*)'Initial local time (in hours, between 0 and 24)?' call getin("time",time) write(*,*)" time = ",time time = time/24. ! convert time (hours) to fraction of sol else call open_startphy("startfi.nc") call get_var("controle",tab_cntrl,found) if (.not. found) then call abort_physic("open_startphy","tabfi: Failed reading array",1) else write(*,*)'tabfi: tab_cntrl',tab_cntrl endif day0 = tab_cntrl(3) day = float(day0) call get_var("Time",time,found) call close_startphy endif !startfiles_1D ! Discretization (Definition of grid and time steps) ! -------------------------------------------------- nlevel = nlayer + 1 nsoil = nsoilmx day_step = 48 ! default value for day_step write(*,*)'Number of time steps per sol?' call getin("day_step",day_step) write(*,*) " day_step = ",day_step ecritphy = day_step ! default value for ecritphy, output every time step ndt = 10 ! default value for ndt write(*,*)'Number of sols to run?' call getin("ndt",ndt) write(*,*) " ndt = ",ndt dayn = day0 + ndt ndt = ndt*day_step dttestphys = daysec/day_step ! Imposed surface pressure ! ------------------------ psurf = 610. ! Default value for psurf write(*,*) 'Surface pressure (Pa)?' if (.not. therestart1D) then call getin("psurf",psurf) else read(3,*) header, psurf endif write(*,*) " psurf = ",psurf ! Reference pressures pa = 20. ! transition pressure (for hybrid coord.) preff = 610. ! reference surface pressure ! Aerosol properties ! ------------------ tauvis = 0.2 ! default value for tauvis (dust opacity) write(*,'("Reference dust opacity at ",f4.0," Pa?")')odpref call getin("tauvis",tauvis) write(*,*) " tauvis = ",tauvis ! Orbital parameters ! ------------------ if (.not. startfiles_1D) then paleomars = .false. ! Default: no water ice reservoir call getin("paleomars",paleomars) if (paleomars) then write(*,*) "paleomars=", paleomars write(*,*) "Orbital parameters from callphys.def" write(*,*) "Enter eccentricity & Lsperi" write(*,*) 'Martian eccentricity (0