Changeset 3060


Ignore:
Timestamp:
Sep 28, 2023, 3:15:23 PM (14 months ago)
Author:
jbclement
Message:

Mars PCM 1D:
Related to commit r3056, correction of bugs and some adaptations of the subroutine 'init_testphys1d'.
JBC

Location:
trunk/LMDZ.MARS
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3058 r3060  
    42324232- update callphys.def.MCD6 to disable Frost metamorphism option
    42334233
    4234 
     4234== 28/09/2023 == JBC
     4235Related to commit r3056, correction of bugs and some adaptations of the subroutine 'init_testphys1d'.
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3056 r3060  
    55contains
    66
    7 SUBROUTINE init_testphys1d(ngrid,nq,nlayer,odpref,ndt,ptif,pks,dttestphys,startfiles_1D,q,zqsat,qsurf,dq,dqdyn, &
    8                            day0,day,time,psurf,tsurf,gru,grv,u,v,w,q2,play,plev,tsoil,temp,albedo,emis,        &
    9                            latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
     7SUBROUTINE init_testphys1d(startfiles_1D,therestart1D,therestartfi,ngrid,nlayer,odpref,nq,ndt,ptif,pks,dttestphys, &
     8                           q,zqsat,qsurf,dq,dqdyn,day0,day,time,psurf,tsurf,gru,grv,u,v,w,q2,play,plev,tsoil,temp, &
     9                           albedo,emis,latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
    1010
    1111use ioipsl_getincom,          only: getin ! To use 'getin'
     
    4747! Arguments
    4848!=======================================================================
     49logical, intent(in) :: startfiles_1D, therestart1D, therestartfi ! Use of "start1D.txt" and "startfi.nc" files
    4950integer, intent(in) :: ngrid, nlayer
    5051real,    intent(in) :: odpref ! DOD reference pressure (Pa)
     
    5556real,                              intent(out) :: ptif, pks
    5657real,                              intent(out) :: dttestphys    ! testphys1d timestep
    57 logical,                           intent(out) :: startfiles_1D ! Use of "start1D.txt" and "startfi.nc" files
    5858real, dimension(:,:), allocatable, intent(out) :: q             ! tracer mixing ratio (e.g. kg/kg)
    5959real, dimension(:),   allocatable, intent(out) :: zqsat         ! useful for (atm_wat_profile=2)
     
    6262integer,                           intent(out) :: day0          ! initial (sol ; =0 at Ls=0) and final date
    6363real,                              intent(out) :: day           ! date during the run
    64 real,                              intent(out) :: time          ! time (0<time<1 ; time=0.5 a midi)
     64real,                              intent(out) :: time          ! time (0<time<1; time=0.5 at noon)
    6565real,                              intent(out) :: psurf         ! Surface pressure
    6666real, dimension(1),                intent(out) :: tsurf         ! Surface temperature
     
    7070real, dimension(nlayer),           intent(out) :: play          ! Pressure at the middle of the layers (Pa)
    7171real, dimension(nlayer + 1),       intent(out) :: plev          ! intermediate pressure levels (pa)
    72 real, dimension(nsoilmx),          intent(out) :: tsoil         ! subsurface soik temperature (K)
     72real, dimension(nsoilmx),          intent(out) :: tsoil         ! subsurface soil temperature (K)
    7373real, dimension(nlayer),           intent(out) :: temp          ! temperature at the middle of the layers
    7474real, dimension(1,1),              intent(out) :: albedo        ! surface albedo
     
    9090
    9191! RV & JBC: Use of "start1D.txt" and "startfi.nc" files
    92 logical                :: found, therestart1D, therestartfi
     92logical                :: found
    9393character(len = 30)    :: header
    9494real, dimension(100)   :: tab_cntrl
     
    118118
    119119!------------------------------------------------------
    120 ! Loading run parameters from "run.def" file
    121 !------------------------------------------------------
    122 ! check if 'run.def' file is around (otherwise reading parameters
    123 ! from callphys.def via getin() routine won't work.
    124 inquire(file = 'run.def',exist = there)
    125 if (.not. there) then
    126     write(*,*) 'Cannot find required file "run.def"'
    127     write(*,*) '  (which should contain some input parameters along with the following line: INCLUDEDEF=callphys.def)'
    128     write(*,*) ' ... might as well stop here ...'
    129     stop
    130 endif
    131 
    132 write(*,*)'Do you want to use "start1D.txt" and "startfi.nc" files?'
    133 startfiles_1D = .false.
    134 call getin("startfiles_1D",startfiles_1D)
    135 write(*,*) " startfiles_1D = ", startfiles_1D
    136 
    137 if (startfiles_1D) then
    138     inquire(file = 'start1D.txt',exist = therestart1D)
    139     if (.not. therestart1D) then
    140         write(*,*) 'There is no "start1D.txt" file!'
    141         write(*,*) 'Initialization is done with default values.'
    142     endif
    143     inquire(file = 'startfi.nc',exist = therestartfi)
    144     if (.not. therestartfi) then
    145         write(*,*) 'There is no "startfi.nc" file!'
    146         write(*,*) 'Initialization is done with default values.'
    147     endif
    148 endif
    149 
    150 !------------------------------------------------------
    151120! Prescribed constants to be set here
    152121!------------------------------------------------------
     
    155124! Mars planetary constants
    156125! ------------------------
    157 rad = 3397200.                   ! mars radius (m) ~3397200 m
    158 omeg = 4.*asin(1.)/(daysec)      ! rotation rate (rad.s-1)
    159 g = 3.72                         ! gravity (m.s-2) ~3.72
    160 mugaz = 43.49                    ! atmosphere mola mass (g.mol-1) ~43.49
    161 rcp = .256793                    ! = r/cp ~0.256793
     126rad = 3397200.            ! mars radius (m) ~3397200 m
     127daysec = 88775.           ! length of a sol (s) ~88775 s
     128omeg = 4.*asin(1.)/daysec ! rotation rate (rad.s-1)
     129g = 3.72                  ! gravity (m.s-2) ~3.72
     130mugaz = 43.49             ! atmosphere mola mass (g.mol-1) ~43.49
     131rcp = .256793             ! = r/cp ~0.256793
    162132r = 8.314511*1000./mugaz
    163133cpp = r/rcp
    164 daysec = 88775.                  ! length of a sol (s) ~88775 s
    165 year_day = 669                   ! length of year (sols) ~668.6
    166 periheli = 206.66                ! minimum sun-mars distance (Mkm) ~206.66
    167 aphelie = 249.22                 ! maximum sun-mars distance (Mkm) ~249.22
    168 halfaxe = 227.94                 ! demi-grand axe de l'ellipse
    169 peri_day = 485.                  ! perihelion date (sols since N. Spring)
    170 obliquit = 25.2                  ! Obliquity (deg) ~25.2
    171 eccentric = 0.0934               ! Eccentricity (0.0934)
     134year_day = 669            ! length of year (sols) ~668.6
     135periheli = 206.66         ! minimum sun-mars distance (Mkm) ~206.66
     136aphelie = 249.22          ! maximum sun-mars distance (Mkm) ~249.22
     137halfaxe = 227.94          ! demi-grand axe de l'ellipse
     138peri_day = 485.           ! perihelion date (sols since N. Spring)
     139obliquit = 25.2           ! Obliquity (deg) ~25.2
     140eccentric = 0.0934        ! Eccentricity (0.0934)
    172141
    173142! Planetary Boundary Layer and Turbulence parameters
     
    202171    stop
    203172else
    204     write(*,*) "testphys1d: Reading file traceur.def"
     173    write(*,*) "init_testphys1d: Reading file traceur.def"
    205174    ! read number of tracers:
    206175    read(90,*,iostat = ierr) nq
    207176    nqtot = nq ! set value of nqtot (in infotrac module) as nq
    208177    if (ierr /= 0) then
    209         write(*,*) "testphys1d: error reading number of tracers"
     178        write(*,*) "init_testphys1d: error reading number of tracers"
    210179        write(*,*) "   (first line of traceur.def) "
    211180        stop
    212181    endif
    213182    if (nq < 1) then
    214         write(*,*) "testphys1d: error number of tracers"
     183        write(*,*) "init_testphys1d: error number of tracers"
    215184        write(*,*) "is nq=",nq," but must be >=1!"
    216185        stop
     
    225194    read(90,'(80a)',iostat = ierr) line ! store the line from traceur.def
    226195    if (ierr /= 0) then
    227         write(*,*) 'testphys1d: error reading tracer names...'
     196        write(*,*) 'init_testphys1d: error reading tracer names...'
    228197        stop
    229198    endif
     
    271240
    272241! Initialize tracers here:
    273 write(*,*) "testphys1d: initializing tracers"
     242write(*,*) "init_testphys1d: initializing tracers"
    274243if (.not. therestart1D) then
    275244    call read_profile(nq,nlayer,qsurf,q)
     
    434403! ovverride iphysiq value that has been set by conf_phys
    435404if (iphysiq /= 1) then
    436     write(*,*) "testphys1d: setting iphysiq=1"
     405    write(*,*) "init_testphys1d: setting iphysiq=1"
    437406    iphysiq = 1
    438407endif
     
    538507enddo
    539508if (igcm_co2 == 0) then
    540     write(*,*) "testphys1d error, missing co2 tracer!"
     509    write(*,*) "init_testphys1d error, missing co2 tracer!"
    541510    stop
    542511endif
     
    725694
    726695END MODULE init_testphys1d_mod
    727 
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F90

    r3056 r3060  
    11PROGRAM testphys1d
    22
     3use ioipsl_getincom,         only: getin ! To use 'getin'
    34use comsoil_h,               only: inertiedat, inertiesoil, nsoilmx
    45use surfdat_h,               only: albedodat, perenial_co2ice, watercap
     
    9495integer                 :: nq = 1 ! number of tracers
    9596real, dimension(1)      :: latitude, longitude, cell_area
    96 
    97 character(len = 2)  :: str2
    98 character(len = 7)  :: str7
    99 character(len = 44) :: txt
     97logical                 :: there
     98character(len = 2)      :: str2
     99character(len = 7)      :: str7
     100character(len = 44)     :: txt
    100101
    101102! RV & JBC: Use of "start1D.txt" and "startfi.nc" files
    102 logical :: startfiles_1D
     103logical :: startfiles_1D, therestart1D, therestartfi
    103104
    104105! JN & JBC: Force atmospheric water profiles
     
    120121!call initcomgeomphy
    121122
    122 call init_testphys1d(ngrid,nq,nlayer,odpref,ndt,ptif,pks,dttestphys,startfiles_1D,q,zqsat,qsurf,dq,dqdyn, &
    123                      day0,day,time,psurf,tsurf,gru,grv,u,v,w,q2,play,plev,tsoil,temp,albedo,emis,         &
    124                      latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
     123!------------------------------------------------------
     124! Loading run parameters from "run.def" file
     125!------------------------------------------------------
     126! check if 'run.def' file is around. Otherwise reading parameters
     127! from callphys.def via getin() routine won't work.
     128inquire(file = 'run.def',exist = there)
     129if (.not. there) then
     130    write(*,*) 'Cannot find required file "run.def"'
     131    write(*,*) '  (which should contain some input parameters along with the following line: INCLUDEDEF=callphys.def)'
     132    write(*,*) ' ... might as well stop here ...'
     133    stop
     134endif
     135
     136write(*,*)'Do you want to use "start1D.txt" and "startfi.nc" files?'
     137startfiles_1D = .false.
     138therestart1D = .false.
     139therestartfi = .false.
     140call getin("startfiles_1D",startfiles_1D)
     141write(*,*) " startfiles_1D = ", startfiles_1D
     142
     143if (startfiles_1D) then
     144    inquire(file = 'start1D.txt',exist = therestart1D)
     145    if (.not. therestart1D) then
     146        write(*,*) 'There is no "start1D.txt" file!'
     147        write(*,*) 'Initialization is done with default values.'
     148    endif
     149    inquire(file = 'startfi.nc',exist = therestartfi)
     150    if (.not. therestartfi) then
     151        write(*,*) 'There is no "startfi.nc" file!'
     152        write(*,*) 'Initialization is done with default values.'
     153    endif
     154endif
     155
     156call init_testphys1d(startfiles_1D,therestart1D,therestartfi,ngrid,nlayer,odpref,nq,ndt,ptif,pks,dttestphys, &
     157                     q,zqsat,qsurf,dq,dqdyn,day0,day,time,psurf,tsurf,gru,grv,u,v,w,q2,play,plev,tsoil,temp, &
     158                     albedo,emis,latitude,longitude,cell_area,atm_wat_profile,atm_wat_tau)
    125159
    126160! Write a "startfi" file
     
    128162! This file will be read during the first call to "physiq".
    129163! It is needed to transfert physics variables to "physiq"...
    130 if (.not. startfiles_1D) then
     164if (.not. therestartfi) then
    131165    call physdem0("startfi.nc",longitude,latitude,nsoilmx,ngrid, &
    132166                  llm,nq,dttestphys,float(day0),0.,cell_area,    &
     
    135169                  tsurf,tsoil,inertiesoil,albedo,emis,q2,qsurf,tauscaling, &
    136170                  totcloudfrac,wstar,watercap,perenial_co2ice)
    137 endif !(.not. startfiles_1D )
     171endif !(.not. therestartfi)
    138172
    139173!=======================================================================
     
    260294!***********************************************************************
    261295!***********************************************************************
    262 
Note: See TracChangeset for help on using the changeset viewer.