Changeset 3051


Ignore:
Timestamp:
Sep 26, 2023, 6:10:40 PM (16 months ago)
Author:
jbclement
Message:

Mars PCM 1D:
Addition of the file "start1D.txt" which mimics a "start.nc" file to be able to run chained simulations in 1D. Like this, key variables and profiles can be got from one run to the next. As a consequence, the subroutine "write_profile.F90" is replaced by "writerestart1D.F90".
JBC

Location:
trunk/LMDZ.MARS
Files:
3 edited
1 moved

Legend:

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

    r3050 r3051  
    42074207
    42084208== 26/09/2023 == JBC
     4209Mars PEM:
    42094210Minor changes concerning the form of the code in the PEM.
     4211Mars PCM 1D:
     4212Addition of the file "start1D.txt" which mimics a "start.nc" file to be able to run chained simulations in 1D. Like this, key variables and profiles can be got from one run to the next. As a consequence, the subroutine "write_profile.F90" is replaced by "writerestart1D.F90".
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F

    r3045 r3051  
    9090      INTEGER ilayer,ilevel,isoil,idt,iq
    9191      LOGICAl firstcall,lastcall
    92       LOGICAL write_prof
    9392c
    9493      real,parameter :: odpref=610. ! DOD reference pressure (Pa)
     
    140139      REAL halfaxe, excentric, Lsperi
    141140      Logical paleomars
    142 c   JN : Force atmospheric water profiles
    143       REAL atm_wat_profile
    144       REAL atm_wat_tau
    145       REAL,ALLOCATABLE :: zqsat(:) ! useful for (atm_wat_profile=2)
    146 
     141
     142c   JN & JBC: Force atmospheric water profiles
     143      real                            :: atm_wat_profile, atm_wat_tau
     144      real, dimension(:), allocatable :: zqsat ! useful for (atm_wat_profile=2)
    147145
    148146c   MVals: isotopes as in the dynamics (CRisi)
     
    152150      INTEGER ierr0
    153151      LOGICAL :: continu
    154 
    155152      logical :: present
    156153
     
    158155      real :: flux_geo_tmp
    159156
    160 c   RV: Start from a startfi and not run.def
    161       logical :: startfile_1D
    162       REAL tab_cntrl(100)
    163       LOGICAL :: found
    164       REAL albedo_read(1,2,1)      ! surface albedo
     157c   RV & JBC: Use of "start1D.txt" and "startfi.nc" files
     158      logical                :: startfiles_1D, found
     159      logical                :: therestart1D, therestartfi
     160      character(len = 30)    :: header
     161      real, dimension(100)   :: tab_cntrl
     162      real, dimension(1,2,1) :: albedo_read(1,2,1) ! surface albedo
    165163
    166164c   LL: Possibility to add subsurface ice
     
    184182!      call initcomgeomphy
    185183
    186 
    187184c ------------------------------------------------------
    188185c  Loading run parameters from "run.def" file
    189186c ------------------------------------------------------
    190 
    191 
    192187! check if 'run.def' file is around (otherwise reading parameters
    193188! from callphys.def via getin() routine won't work.
     
    206201      endif
    207202
    208       write(*,*)'Do you want to start with a startfi and write
    209      & a restartfi?'
    210       startfile_1D=.false.
    211       call getin("startfile_1D",startfile_1D)
    212       write(*,*)" startfile_1D = ", startfile_1D
     203      write(*,*)'Do you want to use "start1D.txt" and "startfi.nc"',
     204     &' files?'
     205      startfiles_1D = .false.
     206      call getin("startfiles_1D",startfiles_1D)
     207      write(*,*) " startfiles_1D = ", startfiles_1D
     208     
     209      if (startfiles_1D) then
     210          inquire(file ='start1D.txt',exist = therestart1D)
     211          if (.not. therestart1D) then
     212              write(*,*) 'There is no "start1D.txt" file!'
     213              write(*,*) 'Initialization is done with default values.'
     214          endif
     215          inquire(file ='startfi.nc',exist = therestartfi)
     216          if (.not. therestartfi) then
     217              write(*,*) 'There is no "startfi.nc" file!'
     218              write(*,*) 'Initialization is done with default values.'
     219          endif
     220      endif
    213221
    214222c ------------------------------------------------------
    215223c  Prescribed constants to be set here
    216224c ------------------------------------------------------
    217 c      if(.not. startfile_1D ) then
    218225      pi=2.E+0*asin(1.E+0)
    219226
     
    253260      dtemisice(1) = 2.          ! time scale for snow metamorphism (north)
    254261      dtemisice(2) = 2.          ! time scale for snow metamorphism (south)
    255 
    256 computeTcondc      endif ! .not. startfile_1D
    257262
    258263c     mesh surface (not a very usefull quantity in 1D)
     
    353358        ! Initialize tracers here:
    354359        write(*,*) "testphys1d: initializing tracers"
    355         call read_profile(nq,nlayer,qsurf,q)
     360        if (.not. therestart1D) then
     361            call read_profile(nq,nlayer,qsurf,q)
     362        else
     363            do iq = 1,nq
     364                open(3,file = 'start1D.txt',status = "old",
     365     &action = "read")
     366                read(3,*) header, qsurf(iq),
     367     & (q(ilayer,iq), ilayer = 1,nlayer)
     368                if (tname(iq) /= trim(header)) then
     369                    write(*,*) 'Tracer names not compatible for',
     370     &' initialization with "start1D.txt"!'
     371                    stop
     372                endif
     373            enddo
     374        endif
    356375
    357376      call init_physics_distribution(regular_lonlat,4,
    358377     &                               1,1,1,nlayer,COMM_LMDZ)
    359378
    360       if(.not. startfile_1D ) then
    361 
    362379c  Date and local time at beginning of run
    363380c  ---------------------------------------
     381      if (.not. startfiles_1D) then
    364382c    Date (in sols since spring solstice) at beginning of run
    365383      day0 = 0 ! default value for day0
     
    391409       call close_startphy
    392410
    393       endif !startfile_1D
     411      endif !startfiles_1D
    394412
    395413c  Discretization (Definition of grid and time steps)
     
    418436      psurf = 610. ! Default value for psurf
    419437      write(*,*) 'Surface pressure (Pa)?'
    420       open(3,file = 'profile_pressure',status = 'old',
    421      &     form = 'formatted',iostat = ierr)
    422       if (ierr == 0) then
    423           write(*,*) 'Reading file ''profile_pressure''...'
    424           read(3,*) psurf
    425           write(*,*) " psurf = ",psurf
     438      if (.not. therestart1D) then
     439          call getin("psurf",psurf)
    426440      else
    427           write(*,*) 'File ''profile_pressure'' not found!'
    428           write(*,*) 'Reading surface pressure in ''callphys.def''',
    429      &' if given...'
    430           call getin("psurf",psurf)
    431           write(*,*) " psurf = ",psurf
     441          read(3,*) header, psurf
    432442      endif
    433       close(3)
     443      write(*,*) " psurf = ",psurf
    434444
    435445c Reference pressures
     
    446456c Orbital parameters
    447457c ------------------
    448       if(.not. startfile_1D ) then
    449 
     458      if (.not. startfiles_1D) then
    450459      paleomars=.false. ! Default: no water ice reservoir
    451460      call getin("paleomars",paleomars)
     
    487496        call getin("obliquit",obliquit)
    488497        write(*,*) " obliquit = ",obliquit
    489       end if
    490 
    491       endif !(.not. startfile_1D )
     498      endif
     499
     500      endif !(.not. startfiles_1D )
    492501 
    493502c  latitude/longitude
     
    533542c  Initialize albedo / soil thermal inertia
    534543c  ----------------------------------------
    535 c
    536 
    537       if(.not. startfile_1D ) then
    538 
     544      if (.not. startfiles_1D) then
    539545      albedodat(1)=0.2 ! default value for albedodat
    540546      write(*,*)'Albedo of bare ground ?'
     
    556562      write(*,*) " z0 = ",z0(1)
    557563
    558       endif !(.not. startfile_1D )
     564      endif !(.not. startfiles_1D )
    559565
    560566! Initialize local slope parameters (only matters if "callslope"
     
    575581c  for the gravity wave scheme
    576582c  ---------------------------------
    577 c
    578583      zmea(1)=0.E+0
    579584      zstd(1)=0.E+0
     
    584589c  for the slope wind scheme
    585590c  ---------------------------------
    586 
    587591      hmons(1)=0.E+0
    588592      write(*,*)'hmons is initialized to ',hmons(1)
     
    593597c  Default values initializing the coefficients calculated later
    594598c  ---------------------------------
    595 
    596599      tauscaling(1)=1. ! calculated in aeropacity_mod.F
    597600      totcloudfrac(1)=1. ! calculated in watercloud_mod.F     
     
    619622      write(*,*) " v = ",grv
    620623
    621 c     Initialize winds  for first time step
    622       DO ilayer=1,nlayer
    623          u(ilayer)=gru
    624          v(ilayer)=grv
    625          w(ilayer)=0 ! default: no vertical wind
    626       ENDDO
     624c     Initialize winds for first time step
     625      if (.not. therestart1D) then
     626          do ilayer = 1,nlayer
     627             u(ilayer) = gru
     628             v(ilayer) = grv
     629          enddo
     630      else
     631          read(3,*) header, (u(ilayer), ilayer = 1,nlayer)
     632          read(3,*) header, (v(ilayer), ilayer = 1,nlayer)
     633      endif
     634      w = 0. ! default: no vertical wind
    627635
    628636c     Initialize turbulente kinetic energy
     
    645653      endif
    646654
    647       if(.not. startfile_1D ) then
     655      if (.not. startfiles_1D) then
    648656      qsurf(igcm_co2)=0.E+0 ! default value for co2ice
    649657      write(*,*)'Initial CO2 ice on the surface (kg.m-2)'
    650658      call getin("co2ice",qsurf(igcm_co2))
    651659      write(*,*) " co2ice = ",qsurf(igcm_co2)
    652       endif !(.not. startfile_1D )
     660      endif !(.not. startfiles_1D )
    653661
    654662c
    655663c  emissivity
    656664c  ----------
    657       if(.not. startfile_1D ) then
     665      if (.not. startfiles_1D) then
    658666      emis=emissiv
    659667      IF (qsurf(igcm_co2).eq.1.E+0) THEN
     
    661669         IF(latitude(1).LT.0) emis=emisice(2) ! southern hemisphere
    662670      ENDIF
    663       endif !(.not. startfile_1D )
     671      endif !(.not. startfiles_1D )
    664672 
    665 
    666673c  Compute pressures and altitudes of atmospheric levels
    667674c  ----------------------------------------------------------------
    668 
    669675c    Vertical Coordinates
    670676c    """"""""""""""""""""
     
    705711      call profile(nlayer+1,tmp1,tmp2)
    706712
    707       tsurf=tmp2(0)
    708       DO ilayer=1,nlayer
    709         temp(ilayer)=tmp2(ilayer)
    710       ENDDO
    711      
     713      if (.not. therestart1D) then
     714          tsurf = tmp2(0)
     715          do ilayer = 1,nlayer
     716              temp(ilayer) = tmp2(ilayer)
     717          enddo
     718      else
     719          read(3,*) header, tsurf, (temp(ilayer), ilayer = 1,nlayer)
     720          close(3)
     721      endif     
    712722
    713723! Initialize soil properties and temperature
     
    715725      volcapa=1.e6 ! volumetric heat capacity
    716726
    717       if(.not. startfile_1D ) then
    718 
     727      if (.not. startfiles_1D) then
    719728! Initialize depths
    720729! -----------------
     
    766775       ENDDO
    767776
    768       endif !(.not. startfile_1D )
     777      endif !(.not. startfiles_1D)
    769778
    770779      flux_geo_tmp=0.
     
    781790      enddo
    782791
    783 c    Initialize traceurs
    784 c    ---------------------------
    785 
     792c Initialize traceurs
     793c ---------------------------
    786794      if (photochem.or.callthermos) then
    787795         write(*,*) 'Initializing chemical species'
     
    809817c Check if the surface is a water ice reservoir
    810818c --------------------------------------------------
    811       if(.not. startfile_1D ) then
    812       watercap(1,:)=0 ! Initialize watercap
    813       endif !(.not. startfile_1D )
     819      if (.not. startfiles_1D) watercap(1,:)=0 ! Initialize watercap
    814820      watercaptag(1)=.false. ! Default: no water ice reservoir
    815821      write(*,*)'Water ice cap on ground ?'
     
    822828      atm_wat_profile = -1. ! Default: free atm wat profile
    823829      if (water) then
    824       write(*,*)'Force atmospheric water vapor profile?'
    825       call getin("atm_wat_profile",atm_wat_profile)
    826       write(*,*) "atm_wat_profile = ", atm_wat_profile
    827       if (abs(atm_wat_profile + 1.) < 1.e-15) then ! if == -1.
    828         write(*,*) "Free atmospheric water vapor profile"
    829         write(*,*) "Total water is conserved in the column"
    830       else if (abs(atm_wat_profile) < 1.e-15) then ! if == 0.
    831         write(*,*) "Dry atmospheric water vapor profile"
    832       else if (0. < atm_wat_profile .and. atm_wat_profile <= 1.) then
    833         write(*,*) "Prescribed atmospheric water vapor profile"
    834         write(*,*) "Unless it reaches saturation (maximal value)"
    835       else
    836         write(*,*) 'Water vapor profile value not correct!'
    837         stop
    838       endif
     830          write(*,*)'Force atmospheric water vapor profile?'
     831          call getin('atm_wat_profile',atm_wat_profile)
     832          write(*,*) 'atm_wat_profile = ', atm_wat_profile
     833          if (abs(atm_wat_profile + 1.) < 1.e-15) then ! if == -1.
     834              write(*,*) 'Free atmospheric water vapor profile'
     835              write(*,*) 'Total water is conserved in the column'
     836          else if (abs(atm_wat_profile) < 1.e-15) then ! if == 0.
     837              write(*,*) 'Dry atmospheric water vapor profile'
     838          else if (0. < atm_wat_profile .and. atm_wat_profile <= 1.)
     839     & then
     840              write(*,*) 'Prescribed atmospheric water vapor profile'
     841              write(*,*) 'Unless it reaches saturation (maximal value)'
     842          else
     843              write(*,*) 'Water vapor profile value not correct!'
     844              stop
     845          endif
    839846      endif
    840847
     
    844851      atm_wat_tau = -1. ! Default: no time relaxation
    845852      if (water) then
    846       write(*,*) 'Relax atmospheric water vapor profile?'
    847       call getin("atm_wat_tau",atm_wat_tau)
    848       write(*,*) "atm_wat_tau = ", atm_wat_tau
    849       if (atm_wat_tau < 0.) then
    850         write(*,*) "Atmospheric water vapor profile is not relaxed"
    851       else
    852         if (0. <= atm_wat_profile .and. atm_wat_profile <= 1.) then
    853           write(*,*) "Relaxed atmospheric water vapor profile towards ",
    854      &    atm_wat_profile
    855           write(*,*) "Unless it reaches saturation (maximal value)"
    856         else
    857        write(*,*) 'Reference atmospheric water vapor profile not known!'
    858        write(*,*) 'Please, specify atm_wat_profile'
    859        stop
    860         endif
    861       endif
     853          write(*,*) 'Relax atmospheric water vapor profile?'
     854          call getin('atm_wat_tau',atm_wat_tau)
     855          write(*,*) 'atm_wat_tau = ', atm_wat_tau
     856          if (atm_wat_tau < 0.) then
     857              write(*,*) 'Atmospheric water vapor profile is not',
     858     &' relaxed.'
     859          else
     860              if (0. <= atm_wat_profile .and. atm_wat_profile <= 1.)
     861     & then
     862                  write(*,*) 'Relaxed atmospheric water vapor profile',
     863     &' towards ', atm_wat_profile
     864                  write(*,*) 'Unless it reaches saturation (maximal',
     865     &' value)'
     866              else
     867                  write(*,*) 'Reference atmospheric water vapor',
     868     &' profile not known!'
     869                  write(*,*) 'Please, specify atm_wat_profile'
     870                  stop
     871              endif
     872          endif
    862873      endif
    863874
     
    867878c  It is needed to transfert physics variables to "physiq"...
    868879
    869       if(.not. startfile_1D ) then
    870 
     880      if (.not. startfiles_1D) then
    871881      call physdem0("startfi.nc",longitude,latitude,nsoilmx,ngrid,
    872882     &              llm,nq,dttestphys,float(day0),0.,cell_area,
     
    877887     &              q2,qsurf,tauscaling,
    878888     &              totcloudfrac,wstar,watercap,perenial_co2ice)
    879       endif !(.not. startfile_1D )
     889      endif !(.not. startfiles_1D )
    880890
    881891c=======================================================================
     
    919929!       ---------------------------------------
    920930      if (water) then
    921         call watersat(nlayer,temp,play,zqsat)
    922         if (0. <= atm_wat_profile .and. atm_wat_profile <= 1.) then
    923         ! If atmospheric water is monitored
    924           if (atm_wat_tau < 0.) then ! Prescribed atm_wat_profile
    925             ! Wet if >0, Dry if =0
    926             q(:,igcm_h2o_vap) = min(zqsat(:),atm_wat_profile*g/psurf)
    927             q(:,igcm_h2o_ice) = 0. ! reset h2o ice
    928           else ! Relaxation towards the value atm_wat_profile with relaxation time atm_wat_tau
    929         q(:,igcm_h2o_vap) = atm_wat_profile*g/psurf + (q(:,igcm_h2o_vap)
    930      &          - atm_wat_profile*g/psurf)*dexp(-dttestphys/atm_wat_tau)
    931             q(:,igcm_h2o_vap) = min(zqsat(:),q(:,igcm_h2o_vap))
    932             q(:,igcm_h2o_ice) = 0. ! reset h2o ice
     931          call watersat(nlayer,temp,play,zqsat)
     932          if (0. <= atm_wat_profile .and. atm_wat_profile <= 1.) then
     933          ! If atmospheric water is monitored
     934              if (atm_wat_tau < 0.) then ! Prescribed atm_wat_profile: wet if >0, dry if =0
     935              q(:,igcm_h2o_vap) = min(zqsat(:),atm_wat_profile*g/psurf)
     936              q(:,igcm_h2o_ice) = 0. ! reset h2o ice
     937              else ! Relaxation towards the value atm_wat_profile with relaxation time atm_wat_tau
     938       q(:,igcm_h2o_vap) = atm_wat_profile*g/psurf + (q(:,igcm_h2o_vap)
     939     &        - atm_wat_profile*g/psurf)*dexp(-dttestphys/atm_wat_tau)
     940              q(:,igcm_h2o_vap) = min(zqsat(:),q(:,igcm_h2o_vap))
     941              q(:,igcm_h2o_ice) = 0. ! reset h2o ice
     942              endif
    933943          endif
    934         endif
    935944      endif
    936945
     
    939948c       --------------------
    940949      CALL physiq (1,llm,nq,firstcall,lastcall,
    941      ,     day,time,dttestphys,plev,play,phi,
    942      ,     u,v,temp,q,w,
     950     .     day,time,dttestphys,plev,play,phi,
     951     .     u,v,temp,q,w,
    943952C - outputs
    944      s     du, dv, dtemp, dq,dpsurf)
     953     .     du, dv, dtemp, dq,dpsurf)
    945954!      write(*,*) "testphys1d apres q", q(1,:)
    946955
     
    9921001
    9931002!       increment tracers
    994         DO iq = 1, nq
     1003        DO iq = 1,nq
    9951004          DO ilayer=1,nlayer
    9961005             q(ilayer,iq)=q(ilayer,iq)+dttestphys*dq(ilayer,iq)
     
    9991008      ENDDO   ! of idt=1,ndt ! end of time stepping loop
    10001009
    1001       ! Update the profile files at the end of the run
    1002       write_prof = .false.
    1003       call getin("write_prof",write_prof)
    1004       if (write_prof) then
    1005           do iq = 1,nq
    1006               call writeprofile(nlayer,noms(iq),qsurf(iq),q(:,iq))
    1007           enddo
    1008           call writeprofile(nlayer,'pressure',psurf,play)
    1009       endif
     1010      ! Writing the "restart1D.txt" file for the next run
     1011      if (startfiles_1D) call writerestart1D(psurf,tsurf,nlayer,temp,
     1012     &u,v,nq,noms,qsurf,q)
     1013 
    10101014
    10111015      write(*,*) "testphys1d: Everything is cool."
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/writerestart1D.F90

    r3050 r3051  
    1 SUBROUTINE writeprofile(nlev,profilename,surfdata,profiledata)
     1SUBROUTINE writerestart1D(psurf,tsurf,nlayer,temp,u,v,nq,qnames,qsurf,q)
    22
    33implicit none
    44
    5 ! arguments
    6 integer, intent(in)               :: nlev
    7 real, intent(in)                  :: surfdata
    8 real, dimension(nlev), intent(in) :: profiledata
    9 character(len = 30), intent(in)   :: profilename
     5! Arguments
     6integer, intent(in)                           :: nlayer, nq
     7real, intent(in)                              :: psurf, tsurf
     8real, dimension(nlayer), intent(in)           :: temp, u, v
     9real, dimension(nlayer,nq), intent(in)        :: q
     10real, dimension(nq), intent(in)               :: qsurf
     11character(len = *), dimension(nq), intent(in) :: qnames
    1012
    11 ! Local
    12 integer :: il
     13! Local variables
     14integer :: il, iq
    1315
    14 ! Write the data
    15 open(1,file = 'profile_out_'//trim(profilename),form = 'formatted')
    16 write(1,*) surfdata
    17 do il = 1,nlev
    18     write(1,*) profiledata(il)
     16! Write the data needed for a restart in "restart1D.txt"
     17open(1,file = 'restart1D.txt',status = "replace",action = "write")
     18do iq = 1,nq
     19    write(1,*) qnames(iq), qsurf(iq), (q(il,iq), il = 1,nlayer)
    1920enddo
     21write(1,*) 'ps', psurf
     22write(1,*) 'u', (u(il), il = 1,nlayer)
     23write(1,*) 'v', (v(il), il = 1,nlayer)
     24write(1,*) 'teta', tsurf, (temp(il), il = 1,nlayer)
    2025close(1)
    21 return
    2226
    23 END
     27END SUBROUTINE writerestart1D
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r2999 r3051  
    224224 
    225225 ! Perenial CO2 ice layer
    226   if(paleoclimate) then
    227     call put_field("perenial_co2ice","CO2 ice cover",perenial_co2ice,time)
    228   endif
     226  if (paleoclimate) call put_field("perenial_co2ice","CO2 ice cover",perenial_co2ice,time)
     227
    229228  ! Surface temperature
    230229  call put_field("tsurf","Surface temperature",tsurf,time)
Note: See TracChangeset for help on using the changeset viewer.