Changeset 2924 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Mar 30, 2023, 10:37:08 AM (20 months ago)
Author:
romain.vande
Message:

1D Mars PCM:
Add the possibility to start the 1d model from a startfi (option startfile_1D in run.def false by default).
It will then write a restartfi at the end of the run.
+ Correction of r2919 for flux geo in 1D and initialize it to 0 by default.
+ Minor correction of iostart error message.
RV

Location:
trunk/LMDZ.MARS
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2922 r2924  
    39643964Add illustrative execution job for spirit (aka MESOIPSL cluster) in deftank
    39653965
     3966==30/03/2023 == RV
     3967Add the possibility to start the 1d model from a startfi (option startfile_1D in run.def false by default).
     3968It will then write a restartfi at the end of the run.
     3969+ Correction of r2919 for flux geo in 1D and initialize it to 0 by default.
     3970+ Minor correction of iostart error message.
     3971
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F

    r2919 r2924  
    66      use mod_grid_phy_lmdz, only : regular_lonlat
    77      use infotrac, only: nqtot, tname, nqperes,nqfils
    8       use comsoil_h, only: volcapa, layer, mlayer, inertiedat, nsoilmx,flux_geo
     8      use comsoil_h, only: volcapa, layer, mlayer, inertiedat, nsoilmx,
     9     &                     flux_geo
    910      use comgeomfi_h, only: sinlat, ini_fillgeom
    1011      use surfdat_h, only: albedodat, z0_default, emissiv, emisice,
     
    1314     &                     watercaptag, watercap, hmons, summit, base
    1415      use slope_mod, only: theta_sl, psi_sl
    15       use comslope_mod, only: def_slope,subslope_dist
     16      use comslope_mod, only: def_slope,subslope_dist,def_slope_mean
    1617      use phyredem, only: physdem0,physdem1
    1718      use geometry_mod, only: init_geometry
     
    3637      USE read_profile_mod, ONLY: read_profile
    3738      use inichim_newstart_mod, only: inichim_newstart
     39      use phyetat0_mod, only: phyetat0
     40      USE netcdf, only: NF90_OPEN, NF90_NOERR, NF90_NOWRITE,
     41     &                  nf90_strerror
     42      use iostart, only: open_startphy,get_var, close_startphy
    3843      IMPLICIT NONE
    3944
     
    146151c   LL: Subsurface geothermal flux
    147152      real :: flux_geo_tmp
     153
     154c   RV: Start from a startfi and not run.def
     155      logical :: startfile_1D
     156      REAL tab_cntrl(100)
     157      LOGICAL :: found
     158      REAL albedo_read(1,2,1)      ! surface albedo
    148159c=======================================================================
    149160
     
    156167!      call initcomgeomphy
    157168
     169
     170c ------------------------------------------------------
     171c  Loading run parameters from "run.def" file
     172c ------------------------------------------------------
     173
     174
     175! check if 'run.def' file is around (otherwise reading parameters
     176! from callphys.def via getin() routine won't work.
     177      open(99,file='run.def',status='old',form='formatted',
     178     &     iostat=ierr)
     179      if (ierr.ne.0) then
     180        write(*,*) 'Cannot find required file "run.def"'
     181        write(*,*) '  (which should contain some input parameters'
     182        write(*,*) '   along with the following line:'
     183        write(*,*) '   INCLUDEDEF=callphys.def'
     184        write(*,*) '   )'
     185        write(*,*) ' ... might as well stop here ...'
     186        stop
     187      else
     188        close(99)
     189      endif
     190
     191      write(*,*)'Do you want to start with a startfi and write
     192     &           a restartfi?'
     193      startfile_1D=.false.
     194      call getin("startfile_1D",startfile_1D)
     195      write(*,*)" startfile_1D = ", startfile_1D
     196
    158197c ------------------------------------------------------
    159198c  Prescribed constants to be set here
    160199c ------------------------------------------------------
     200
     201c      if(.not. startfile_1D ) then
    161202
    162203      pi=2.E+0*asin(1.E+0)
     
    196237      iceradius(2) = 100.e-6     ! mean scat radius of CO2 snow (south)
    197238      dtemisice(1) = 2.          ! time scale for snow metamorphism (north)
    198       dtemisice(2) = 2.          ! time scale for snow metamorphism (south
     239      dtemisice(2) = 2.          ! time scale for snow metamorphism (south)
     240
     241c      endif ! .not. startfile_1D
    199242
    200243c     mesh surface (not a very usefull quantity in 1D)
    201244c     ----------------------------------------------------
    202245      cell_area(1)=1.E+0
    203      
    204 c ------------------------------------------------------
    205 c  Loading run parameters from "run.def" file
    206 c ------------------------------------------------------
    207 
    208 
    209 ! check if 'run.def' file is around (otherwise reading parameters
    210 ! from callphys.def via getin() routine won't work.
    211       open(99,file='run.def',status='old',form='formatted',
    212      &     iostat=ierr)
    213       if (ierr.ne.0) then
    214         write(*,*) 'Cannot find required file "run.def"'
    215         write(*,*) '  (which should contain some input parameters'
    216         write(*,*) '   along with the following line:'
    217         write(*,*) '   INCLUDEDEF=callphys.def'
    218         write(*,*) '   )'
    219         write(*,*) ' ... might as well stop here ...'
    220         stop
    221       else
    222         close(99)
    223       endif
    224246
    225247
     
    320342        call read_profile(nq, nlayer, qsurf, q)
    321343
     344      call init_physics_distribution(regular_lonlat,4,
     345     &                               1,1,1,nlayer,1)
     346
     347      if(.not. startfile_1D ) then
     348
    322349c  Date and local time at beginning of run
    323350c  ---------------------------------------
     
    335362      time=time/24.E+0 ! convert time (hours) to fraction of sol
    336363
     364      else
     365      call open_startphy("startfi.nc")
     366      call get_var("controle",tab_cntrl,found)
     367       if (.not.found) then
     368         call abort_physic("open_startphy",
     369     &        "tabfi: Failed reading <controle> array",1)
     370       else
     371         write(*,*)'tabfi: tab_cntrl',tab_cntrl
     372       endif
     373       day0 = tab_cntrl(3)
     374       day=float(day0)
     375
     376       call get_var("Time",time,found)
     377
     378       call close_startphy
     379
     380      endif !startfile_1D
     381
    337382c  Discretization (Definition of grid and time steps)
    338383c  --------------
     
    360405c ------------------------------------
    361406c
     407
    362408      psurf=610. ! default value for psurf
    363409      PRINT *,'Surface pressure (Pa) ?'
    364410      call getin("psurf",psurf)
    365411      write(*,*) " psurf = ",psurf
     412
    366413c Reference pressures
    367414      pa=20.   ! transition pressure (for hybrid coord.)
     
    377424c Orbital parameters
    378425c ------------------
     426
     427      if(.not. startfile_1D ) then
     428
    379429      paleomars=.false. ! Default: no water ice reservoir
    380430      call getin("paleomars",paleomars)
     
    417467        write(*,*) " obliquit = ",obliquit
    418468      end if
     469
     470      endif !(.not. startfile_1D )
    419471 
    420472c  latitude/longitude
     
    433485!Mars possible matter with dtphys in input and include!!!
    434486! Initializations below should mimick what is done in iniphysiq for 3D GCM
    435       call init_physics_distribution(regular_lonlat,4,
    436      &                               1,1,1,nlayer,1)
    437487      call init_interface_dyn_phys
    438488      call init_regular_lonlat(1,1,longitude,latitude,
     
    463513c  ----------------------------------------
    464514c
     515
     516      if(.not. startfile_1D ) then
     517
    465518      albedodat(1)=0.2 ! default value for albedodat
    466519      PRINT *,'Albedo of bare ground ?'
     
    478531      call getin("z0",z0(1))
    479532      write(*,*) " z0 = ",z0(1)
     533
     534      endif !(.not. startfile_1D )
    480535
    481536! Initialize local slope parameters (only matters if "callslope"
     
    564619        stop
    565620      endif
     621
     622      if(.not. startfile_1D ) then
    566623      qsurf(igcm_co2)=0.E+0 ! default value for co2ice
    567624      PRINT *,'Initial CO2 ice on the surface (kg.m-2)'
    568625      call getin("co2ice",qsurf(igcm_co2))
    569626      write(*,*) " co2ice = ",qsurf(igcm_co2)
     627      endif !(.not. startfile_1D )
    570628
    571629c
    572630c  emissivity
    573631c  ----------
     632      if(.not. startfile_1D ) then
    574633      emis=emissiv
    575634      IF (qsurf(igcm_co2).eq.1.E+0) THEN
     
    577636         IF(latitude(1).LT.0) emis=emisice(2) ! southern hemisphere
    578637      ENDIF
    579 
     638      endif !(.not. startfile_1D )
    580639 
    581640
     
    632691! ------------------------------------------
    633692      volcapa=1.e6 ! volumetric heat capacity
     693      if(.not. startfile_1D ) then
    634694      DO isoil=1,nsoil
    635695         inertiedat(1,isoil)=inertiedat(1,1) ! soil thermal inertia
    636696         tsoil(isoil)=tsurf(1)  ! soil temperature
    637697      ENDDO
    638 
     698      endif !(.not. startfile_1D )
     699
     700      flux_geo_tmp=0.
    639701      call getin("flux_geo",flux_geo_tmp)
    640702      flux_geo(:,:) = flux_geo_tmp
    641703
    642 
    643 
    644 
    645 flux_geo
    646704! Initialize depths
    647705! -----------------
     
    681739c Check if the surface is a water ice reservoir
    682740c --------------------------------------------------
     741      if(.not. startfile_1D ) then
    683742      watercap(1,:)=0 ! Initialize watercap
     743      endif !(.not. startfile_1D )
    684744      watercaptag(1)=.false. ! Default: no water ice reservoir
    685745      print *,'Water ice cap on ground ?'
     
    723783c  It is needed to transfert physics variables to "physiq"...
    724784
    725       call physdem0("startfi.nc",longitude,latitude,nsoilmx,ngrid,llm,
    726      &              nq,dtphys,float(day0),0.,cell_area,
     785      if(.not. startfile_1D ) then
     786
     787      call physdem0("startfi.nc",longitude,latitude,nsoilmx,ngrid,
     788     &              llm,nq,dtphys,float(day0),0.,cell_area,
    727789     &              albedodat,inertiedat,def_slope,subslope_dist)
    728790      call physdem1("startfi.nc",nsoilmx,ngrid,llm,nq,
     
    730792     &              tsurf,tsoil,albedo,emis,q2,qsurf,tauscaling,
    731793     &              totcloudfrac,wstar,watercap)
     794      else
     795         CALL phyetat0 ("startfi.nc",0,0,
     796     &         nsoilmx,ngrid,nlayer,nq,
     797     &         day0,time,
     798     &         tsurf,tsoil,albedo_read,emis,
     799     &         q2,qsurf,tauscaling,totcloudfrac,wstar,
     800     &         watercap,def_slope,def_slope_mean,subslope_dist)
     801         day=real(day0)
     802         albedo(1,1)=albedo_read(1,1,1)
     803      endif !(.not. startfile_1D )
    732804
    733805c=======================================================================
     
    737809      firstcall=.true.
    738810      lastcall=.false.
    739 
    740811      DO idt=1,ndt
    741 c        IF (idt.eq.ndt) lastcall=.true.
    742         IF (idt.eq.ndt-day_step-1) then       !test
    743          lastcall=.true.
    744          call solarlong(day*1.0,zls)
    745          write(103,*) 'Ls=',zls*180./pi
    746          write(103,*) 'Lat=', latitude(1)*180./pi
    747          write(103,*) 'Tau=', tauvis/odpref*psurf
    748          write(103,*) 'RunEnd - Atmos. Temp. File'
    749          write(103,*) 'RunEnd - Atmos. Temp. File'
    750          write(104,*) 'Ls=',zls*180./pi
    751          write(104,*) 'Lat=', latitude(1)
    752          write(104,*) 'Tau=', tauvis/odpref*psurf
    753          write(104,*) 'RunEnd - Atmos. Temp. File'
    754         ENDIF
     812        IF (idt.eq.ndt) lastcall=.true.
     813c        IF (idt.eq.ndt-day_step-1) then       !test
     814c         lastcall=.true.
     815c         call solarlong(day*1.0,zls)
     816c         write(103,*) 'Ls=',zls*180./pi
     817c         write(103,*) 'Lat=', latitude(1)*180./pi
     818c         write(103,*) 'Tau=', tauvis/odpref*psurf
     819c         write(103,*) 'RunEnd - Atmos. Temp. File'
     820c         write(103,*) 'RunEnd - Atmos. Temp. File'
     821c         write(104,*) 'Ls=',zls*180./pi
     822c         write(104,*) 'Lat=', latitude(1)
     823c         write(104,*) 'Tau=', tauvis/odpref*psurf
     824c         write(104,*) 'RunEnd - Atmos. Temp. File'
     825c        ENDIF
    755826
    756827c     compute geopotential
     
    879950        CALL endg1d(1,nlayer,zlay/1000.,ndt)
    880951
     952c      if(startfile_1D) then
     953c       call physdem0("restartfi.nc",longitude,latitude,nsoilmx,ngrid,
     954c     &              llm,nq,dtphys,float(day0),0.,cell_area,
     955c     &              albedodat,inertiedat,def_slope,subslope_dist)
     956c       call physdem1("restartfi.nc",nsoilmx,ngrid,llm,nq,
     957c     &              dtphys,time,
     958c     &              tsurf,tsoil,albedo,emis,q2,qsurf,tauscaling,
     959c     &              totcloudfrac,wstar,watercap)
     960c      endif! startfile_1D
     961
    881962      write(*,*) "testphys1d: Everything is cool."
    882963
  • trunk/LMDZ.MARS/libf/phymars/iostart.F90

    r2913 r2924  
    424424 
    425425      ierr=NF90_INQ_VARID(nid_start,var_name,varid)
    426      
    427426      IF (ierr==NF90_NOERR) THEN
    428427        ierr=NF90_GET_VAR(nid_start,varid,var)
     
    10491048      ierr=NF90_DEF_VAR(nid_restart,var_name,NF90_FLOAT,(/idim1d/),nvarid)
    10501049#endif
     1050     
    10511051      ! Add a "title" attribute
    10521052      IF (LEN_TRIM(title)>0) ierr=NF90_PUT_ATT(nid_restart,nvarid,"title",title)
     
    10581058        write(*,*)'put_var_rgen: problem writing '//trim(var_name)
    10591059        write(*,*)trim(nf90_strerror(ierr))
    1060         CALL abort_physic("get_var_rgen","Failed writing variable",1)
     1060        CALL abort_physic("put_var_rgen","Failed writing variable",1)
    10611061      ENDIF
    10621062    ENDIF ! of IF (is_master)
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2916 r2924  
    109109     &                        major_slope,compute_meshgridavg,
    110110     &                        ini_comslope_h
    111 
     111      USE ioipsl_getincom, only: getin
    112112      IMPLICIT NONE
    113113c=======================================================================
     
    545545
    546546      logical :: write_restart
     547      logical,save :: startfile_1D
    547548
    548549c=======================================================================
     
    748749
    749750#ifndef MESOSCALE
    750 
    751          if (ngrid.ne.1) then
     751      startfile_1D=.false.
     752      call getin("startfile_1D",startfile_1D)
     753         if (ngrid.ne.1 .or. startfile_1D) then
    752754           ! no need to compute slopes when in 1D; it is an input
    753755           if (callslope) call getslopes(ngrid,phisfi)
     
    25492551c        ----------------------------------------------------------
    25502552
    2551       IF (ngrid.NE.1) THEN
     2553        IF (startfile_1D) THEN
    25522554
    25532555#ifndef MESOSCALE
     
    26102612     .                emis,q2,qsurf,tauscaling,totcloudfrac,wstar,
    26112613     .                watercap)
    2612          
    2613          ENDIF ! of IF (write_restart)
     2614          ENDIF ! of IF (write_restart)
     2615
    26142616#endif
     2617
     2618         ENDIF ! startfile_1D
     2619
     2620         IF (ngrid.NE.1) then
    26152621
    26162622c        -------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.