Ignore:
Timestamp:
Feb 7, 2024, 12:14:38 PM (17 months ago)
Author:
jbclement
Message:

Mars PCM:

  • Addition of the possibility to use subslopes parametization in 1D. To do so, put 'nslope=x' in "run.def" where x (1, 3, 5 or 7) is the number of slopes you want to, or modify it in an appropriate "startfi.nc". Then, default subslopes definition and distribution are used by the model. The already existing case of using one slope whose inclination and orientation are defined in "run.def" is still possible.
  • Some cleanings throughout the code, in particular related to unused variables.

JBC

Location:
trunk/LMDZ.MARS/libf/phymars/dyn1d
Files:
2 edited

Legend:

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

    r3200 r3203  
    55contains
    66
    7 SUBROUTINE init_testphys1d(start1Dname,startfiname,startfiles_1D,therestart1D,therestartfi,ngrid,nlayer,odpref, &
     7SUBROUTINE init_testphys1d(start1Dname,startfiname,therestart1D,therestartfi,ngrid,nlayer,odpref, &
    88                           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,CO2cond_ps)
     
    1515use surfdat_h,                only: albedodat, z0_default, z0, emissiv, emisice, albedice, iceradius, dtemisice,      &
    1616                                    zmea, zstd, zsig, zgam, zthe, hmons, summit, base, phisfi, watercaptag, watercap, &
    17                                     tsurf, emis, qsurf, perennial_co2ice
     17                                    tsurf, emis, qsurf, perennial_co2ice, ini_surfdat_h_slope_var, end_surfdat_h_slope_var
    1818use infotrac,                 only: nqtot, tname, nqperes, nqfils
    1919use read_profile_mod,         only: read_profile
    2020use iostart,                  only: open_startphy, get_var, close_startphy
    2121use physics_distribution_mod, only: init_physics_distribution
    22 use comsoil_h,                only: volcapa, nsoilmx, inertiesoil, inertiedat, layer, mlayer, flux_geo, tsoil, qsoil
     22use comsoil_h,                only: volcapa, nsoilmx, inertiesoil, inertiedat, layer, mlayer, flux_geo, tsoil, qsoil, &
     23                                    ini_comsoil_h_slope_var, end_comsoil_h_slope_var
    2324use comvert_mod,              only: ap, bp, aps, bps, pa, preff, presnivs, pseudoalt, scaleheight
    24 use dimradmars_mod,           only: tauvis, totcloudfrac, albedo
     25use dimradmars_mod,           only: tauvis, totcloudfrac, albedo, ini_dimradmars_mod_slope_var, end_dimradmars_mod_slope_var
    2526use regular_lonlat_mod,       only: init_regular_lonlat
    2627use mod_interface_dyn_phys,   only: init_interface_dyn_phys
     
    4041use nonoro_gwd_ran_mod,       only: du_nonoro_gwd, dv_nonoro_gwd
    4142use conf_phys_mod,            only: conf_phys
    42 use paleoclimate_mod,         only: paleoclimate
     43use paleoclimate_mod,         only: paleoclimate, ini_paleoclimate_h, end_paleoclimate_h
    4344use comslope_mod,             only: nslope, subslope_dist, ini_comslope_h, end_comslope_h
    4445! Mostly for XIOS outputs:
     
    5455!=======================================================================
    5556integer,      intent(in) :: ngrid, nlayer
    56 real,         intent(in) :: odpref                                    ! DOD reference pressure (Pa)
    57 character(*), intent(in) :: start1Dname, startfiname                  ! Name of starting files for 1D
    58 logical,      intent(in) :: startfiles_1D, therestart1D, therestartfi ! Use of starting files for 1D
     57real,         intent(in) :: odpref                     ! DOD reference pressure (Pa)
     58character(*), intent(in) :: start1Dname, startfiname   ! Name of starting files for 1D
     59logical,      intent(in) :: therestart1D, therestartfi ! Use of starting files for 1D
    5960
    6061integer, intent(inout) :: nq
     
    9697character(30)          :: header
    9798real, dimension(100)   :: tab_cntrl
    98 real, dimension(1,2,1) :: albedo_read ! surface albedo
    9999
    100100! New flag to compute paleo orbital configurations + few variables JN
     
    103103
    104104! MVals: isotopes as in the dynamics (CRisi)
    105 integer                                  :: ifils, ipere, generation, ierr0
     105integer                                  :: ipere, ierr0
    106106character(30), dimension(:), allocatable :: tnom_transp ! transporting fluid short name
    107107character(80)                            :: line        ! to store a line of text
     
    112112real    :: inertieice = 2100. ! ice thermal inertia
    113113integer :: iref
    114 
    115 ! LL: Subsurface geothermal flux
    116 real :: flux_geo_tmp
    117114
    118115!=======================================================================
     
    122119! Prescribed constants to be set here
    123120!------------------------------------------------------
    124 
    125121! Mars planetary constants
    126122! ------------------------
     
    147143lmixmin = 30       ! mixing length ~100
    148144
    149 ! cap properties and surface emissivities
     145! Cap properties and surface emissivities
    150146! ---------------------------------------
    151147emissiv = 0.95         ! Bare ground emissivity ~.95
     
    159155dtemisice(2) = 2.      ! time scale for snow metamorphism (south)
    160156
    161 ! mesh surface (not a very usefull quantity in 1D)
     157! Mesh surface (not a very usefull quantity in 1D)
    162158! ------------------------------------------------
    163159cell_area(1) = 1.
    164160
    165 ! check if there is a 'traceur.def' file and process it
    166 ! load tracer names from file 'traceur.def'
     161! Check if there is a 'traceur.def' file and process it
     162! Load tracer names from file 'traceur.def'
     163! -----------------------------------------------------
    167164open(90,file = 'traceur.def',status = 'old',form = 'formatted',iostat = ierr)
    168165if (ierr /= 0) then
     
    188185endif
    189186
    190 ! allocate arrays:
     187! Allocate arrays
    191188allocate(tname(nq),q(1,nlayer,nq),zqsat(nlayer))
    192189allocate(dq(1,nlayer,nq),dqdyn(1,nlayer,nq),tnom_transp(nq))
    193190
    194 ! read tracer names from file traceur.def
     191! Read tracer names from file traceur.def
    195192do iq = 1,nq
    196193    read(90,'(80a)',iostat = ierr) line ! store the line from traceur.def
     
    281278nsoil = nsoilmx
    282279
    283 day_step = 48 ! default value for day_step
     280day_step = 48 ! Default value for day_step
    284281write(*,*)'Number of time steps per sol?'
    285282call getin("day_step",day_step)
    286283write(*,*) " day_step = ",day_step
    287284
    288 ecritphy = day_step ! default value for ecritphy, output every time step
    289 
    290 ndt = 10 ! default value for ndt
     285ecritphy = day_step ! Default value for ecritphy, output every time step
     286
     287ndt = 10 ! Default value for ndt
    291288write(*,*)'Number of sols to run?'
    292289call getin("ndt",ndt)
     
    311308! Coefficient to control the surface pressure change
    312309! To be defined in "callphys.def" so that the PEM can read it asa well
     310! --------------------------------------------------------------------
    313311CO2cond_ps = 1. ! Default value
    314312write(*,*) 'Coefficient to control the surface pressure change?'
     
    320318
    321319! Reference pressures
    322 pa = 20.     ! transition pressure (for hybrid coord.)
    323 preff = 610. ! reference surface pressure
     320pa = 20.     ! Transition pressure (for hybrid coord.)
     321preff = 610. ! Reference surface pressure
    324322
    325323! Aerosol properties
    326324! ------------------
    327 tauvis = 0.2 ! default value for tauvis (dust opacity)
     325tauvis = 0.2 ! Default value for tauvis (dust opacity)
    328326write(*,'("Reference dust opacity at ",f4.0," Pa?")')odpref
    329327call getin("tauvis",tauvis)
     
    408406endif
    409407
    410 ! Initialize tracers (surface and atmosphere) here:
     408! Initialize local slope parameters
     409! ---------------------------------
     410nslope = 1 ! default: one slope
     411if (.not. therestartfi) then
     412    ! Number of subgrid scale slopes
     413    write(*,*)'Number of slopes?'
     414    call getin("nslope",nslope)
     415    write(*,*) " nslope = ", nslope
     416    call end_comslope_h
     417    call ini_comslope_h(1,nslope)
     418    select case (nslope)
     419        case(1)
     420            ! Sub-slopes parameters (minimum/maximun angles)
     421            def_slope(1) = -90.
     422            def_slope(2) = 90.
     423            ! Fraction of subslopes in mesh
     424            subslope_dist(1,1) = 1.
     425        case(3)
     426            ! Sub-slopes parameters (minimum/maximun angles)
     427            def_slope(1) = -50.
     428            def_slope(2) = -3.
     429            def_slope(3) = 3.
     430            def_slope(4) = 50.
     431            ! Fraction of subslopes in mesh
     432            subslope_dist(1,1) = 0.1
     433            subslope_dist(1,2) = 0.8
     434            subslope_dist(1,3) = 0.1
     435        case(5)
     436            ! Sub-slopes parameters (minimum/maximun angles)
     437            def_slope(1) = -43.
     438            def_slope(2) = -9.
     439            def_slope(3) = -3.
     440            def_slope(4) = 3.
     441            def_slope(5) = 9.
     442            def_slope(6) = 43.
     443            ! Fraction of subslopes in mesh
     444            subslope_dist(1,1) = 0.025
     445            subslope_dist(1,2) = 0.075
     446            subslope_dist(1,3) = 0.8
     447            subslope_dist(1,4) = 0.075
     448            subslope_dist(1,5) = 0.025
     449        case(7)
     450            ! Sub-slopes parameters (minimum/maximun angles)
     451            def_slope(1) = -43.
     452            def_slope(2) = -19.
     453            def_slope(3) = -9.
     454            def_slope(4) = -3.
     455            def_slope(5) = 3.
     456            def_slope(6) = 9.
     457            def_slope(7) = 19.
     458            def_slope(8) = 43.
     459            ! Fraction of subslopes in mesh
     460            subslope_dist(1,1) = 0.01
     461            subslope_dist(1,2) = 0.02
     462            subslope_dist(1,3) = 0.06
     463            subslope_dist(1,4) = 0.8
     464            subslope_dist(1,5) = 0.06
     465            subslope_dist(1,6) = 0.02
     466            subslope_dist(1,7) = 0.01
     467        case default
     468            error stop 'Number of slopes not possible: nslope should be 1, 3, 5 or 7!'
     469    end select
     470
     471    call end_surfdat_h_slope_var
     472    call ini_surfdat_h_slope_var(1,nq,nslope)
     473    call end_comsoil_h_slope_var
     474    call ini_comsoil_h_slope_var(1,nslope)
     475    call end_dimradmars_mod_slope_var
     476    call ini_dimradmars_mod_slope_var(1,nslope)
     477    call end_paleoclimate_h
     478    call ini_paleoclimate_h(1,nslope)
     479
     480    ! Fraction of subslopes in mesh
     481    !write(*,*)'What subslope distribution do you want to use?'
     482    !call getin("slope_distribution",subslope_dist)
     483    !write(*,*) " subslope_dist = ", subslope_dist(1,:)
     484endif
     485
     486! Slope inclination angle (deg) 0: horizontal, 90: vertical
     487theta_sl = 0. ! default: no inclination
     488call getin("slope_inclination",theta_sl)
     489
     490! Slope orientation (deg)
     491! 0 == Northward, 90 == Eastward, 180 == Southward, 270 == Westward
     492psi_sl = 0. ! default value
     493call getin("slope_orientation",psi_sl)
     494
     495! Initialize tracers (surface and atmosphere)
     496!--------------------------------------------
    411497write(*,*) "init_testphys1d: initializing tracers"
    412498if (.not. therestart1D) then
    413499    call read_profile(nq,nlayer,qsurf(1,:,1),q)
     500    do iq = 1,nq
     501        qsurf(1,iq,:) = qsurf(1,iq,1)
     502    enddo
    414503else
    415504    do iq = 1,nq
     
    430519    call getin("albedo",albedodat(1))
    431520    write(*,*) " albedo = ",albedodat(1)
    432     albedo(1,:,1) = albedodat(1)
     521    albedo(1,:,:) = albedodat(1)
    433522
    434523    inertiedat(1,1) = 400 ! default value for inertiedat
     
    446535    write(*,*) " z0 = ",z0(1)
    447536endif !(.not. therestartfi)
    448 
    449 ! Initialize local slope parameters (only matters if "callslope"
    450 ! is .true. in callphys.def)
    451 ! slope inclination angle (deg) 0: horizontal, 90: vertical
    452 theta_sl(1) = 0. ! default: no inclination
    453 call getin("slope_inclination",theta_sl(1))
    454 ! slope orientation (deg)
    455 ! 0 == Northward, 90 == Eastward, 180 == Southward, 270 == Westward
    456 psi_sl(1) = 0. ! default value
    457 call getin("slope_orientation",psi_sl(1))
    458 
    459 ! Sub-slopes parameters (assuming no sub-slopes distribution for now).
    460 def_slope(1) = -90 ! minimum slope angle
    461 def_slope(2) = 90  ! maximum slope angle
    462 subslope_dist(1,1) = 1 ! fraction of subslopes in mesh
    463537
    464538! For the gravity wave scheme
     
    508582
    509583! Initialize winds for first time step
     584!-------------------------------------
    510585if (.not. therestart1D) then
    511586    u = gru
     
    518593
    519594! Initialize turbulent kinetic energy
     595!------------------------------------
    520596q2 = 0.
    521597
    522598! CO2 ice on the surface
    523599! ----------------------
    524 
    525600if (.not. therestartfi) then
    526     qsurf(1,igcm_co2,1) = 0. ! default value for co2ice
     601    qsurf(1,igcm_co2,:) = 0. ! default value for co2ice
    527602    write(*,*)'Initial CO2 ice on the surface (kg.m-2)'
    528603    call getin("co2ice",qsurf(1,igcm_co2,1))
     604    qsurf(1,igcm_co2,:) = qsurf(1,igcm_co2,1)
    529605    write(*,*) " co2ice = ",qsurf(1,igcm_co2,1)
    530606endif !(.not. therestartfi)
     
    533609! ----------
    534610if (.not. therestartfi) then
    535     emis(:,1) = emissiv
     611    emis = emissiv
    536612    if (qsurf(1,igcm_co2,1) == 1.) then
    537         emis(:,1) = emisice(1) ! northern hemisphere
    538         if (latitude(1) < 0) emis(:,1) = emisice(2) ! southern hemisphere
     613        emis = emisice(1) ! northern hemisphere
     614        if (latitude(1) < 0) emis = emisice(2) ! southern hemisphere
    539615    endif
    540616endif !(.not. therestartfi)
     
    568644
    569645if (.not. therestart1D) then
    570     tsurf(:,1) = tmp2(0)
     646    tsurf = tmp2(0)
    571647    temp = tmp2(1:)
    572648else
     
    610686    endif ! ice_depth > 0
    611687
    612     inertiesoil(1,:,1) = inertiedat(1,:)
    613     tsoil(:,:,1) = tsurf(1,1) ! soil temperature
     688    do isoil = 1,nsoil
     689        inertiesoil(1,isoil,:) = inertiedat(1,isoil)
     690        tsoil(1,isoil,:) = tsurf(1,:) ! soil temperature
     691    enddo
    614692endif !(.not. therestartfi)
    615693
    616 flux_geo_tmp = 0.
    617 call getin("flux_geo",flux_geo_tmp)
    618 flux_geo(:,:) = flux_geo_tmp
     694! Initialize subsurface geothermal flux
     695! -------------------------------------
     696flux_geo = 0.
     697call getin("flux_geo",flux_geo(1,1))
     698write(*,*) " flux_geo = ",flux_geo(1,1)
     699flux_geo = flux_geo(1,1)
    619700
    620701! Initialize soil content
    621 ! -----------------
     702! -----------------------
    622703if (.not. therestartfi) qsoil = 0.
    623704
  • TabularUnified trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F90

    r3201 r3203  
    77use watersat_mod,        only: watersat
    88use tracer_mod,          only: igcm_h2o_vap, igcm_h2o_ice, igcm_co2, noms
    9 use comcstfi_h,          only: pi, rad, omeg, g, mugaz, rcp, r, cpp
     9use comcstfi_h,          only: pi, g, rcp, cpp
    1010use time_phylmdz_mod,    only: daysec, day_step
    1111use dimradmars_mod,      only: tauvis, totcloudfrac, albedo
    1212use dust_param_mod,      only: tauscaling
    13 use comvert_mod,         only: ap, bp, aps, bps, pa, preff, sig
     13use comvert_mod,         only: ap, bp, aps, bps
    1414use physiq_mod,          only: physiq
    1515use turb_mod,            only: q2
     
    6363integer, parameter                  :: nlayer = llm
    6464real, parameter                     :: odpref = 610. ! DOD reference pressure (Pa)
    65 integer                             :: unitstart     ! unite d'ecriture de "startfi"
    66 integer                             :: ndt, ilayer, ilevel, isoil, idt, iq
     65integer                             :: ndt, ilayer, idt
    6766logical                             :: firstcall, lastcall
    6867integer                             :: day0          ! initial (sol ; =0 at Ls=0)
     
    8180
    8281! Physical and dynamical tendencies (e.g. m.s-2, K/s, Pa/s)
    83 real, dimension(nlayer)             :: du, dv, dtemp, dudyn, dvdyn, dtempdyn
     82real, dimension(nlayer)             :: du, dv, dtemp
    8483real, dimension(1)                  :: dpsurf
    8584real, dimension(:,:,:), allocatable :: dq, dqdyn
    8685
    8786! Various intermediate variables
    88 integer                 :: aslun
    89 real                    :: zls, pks, ptif, qtotinit, qtot
     87real                    :: zls, pks, ptif
    9088real, dimension(nlayer) :: phi, h, s, w
    9189integer                 :: nq = 1 ! number of tracers
    9290real, dimension(1)      :: latitude, longitude, cell_area
    93 character(2)            :: str2
    94 character(7)            :: str7
    95 character(44)           :: txt
    9691
    9792! RV & JBC: Use of starting files for 1D
     
    148143endif
    149144
    150 call init_testphys1d('start1D.txt','startfi.nc',startfiles_1D,therestart1D,therestartfi,ngrid,nlayer,odpref, &
    151                      nq,q,time,psurf,u,v,temp,ndt,ptif,pks,dttestphys,zqsat,dq,dqdyn,day0,day,gru,grv,w,    &
     145call init_testphys1d('start1D.txt','startfi.nc',therestart1D,therestartfi,ngrid,nlayer,odpref,nq,q, &
     146                     time,psurf,u,v,temp,ndt,ptif,pks,dttestphys,zqsat,dq,dqdyn,day0,day,gru,grv,w, &
    152147                     play,plev,latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau,CO2cond_ps)
    153148
Note: See TracChangeset for help on using the changeset viewer.