Ignore:
Timestamp:
May 25, 2012, 8:06:39 PM (13 years ago)
Author:
acolaitis
Message:

LES RESTART
===========

Several corrections for LES restart. Added a number of save variables from physiq to restart netcdf, so that continuity between runs can truly be achieved.
Added some lines in makemeso so that debug option "-g" also works for WRF (in addtion to the GCM physics) when compiling with ifort

===============================
WARNING WARNING WARNING WARNING
===============================

  • FROM THIS REVISION, YOU MUST MODIFY MANUALLY SOME FILES AS FOLLOW, BEFORE YOU CAN RE COMPILE THE LES :

simply copy the call_meso_physiq*.inc files in $MMM/SRC/WRFV2/ into $MMM/SRC/LES/WRFV2/.
=>> this is usually done during LES installation by $MMM/SRC/LES/LMD_LES_MARS_install

  • IF YOU WANT TO MAKE A RUN WITH RESTART FILES, YOU MUST MAKE A CLEAN RECOMPILATION OF THE MODEL WITH THE UPDATED REGISTRY AND UPDATED GCM FILES

=>> it is advised to remove your working directory (ex: lesnewphys_mpifort64) and start again with makemeso

  • IF YOU WANT TO MAKE A RUN AND GENERATE RESTART FILES, YOU MUST RECOMPILE THE IDEAL.EXE STEP AND PERFORM IT

=>> current wrfinput will not work, as it does not contain the new variables
===============================
WARNING WARNING WARNING WARNING
===============================

Location:
trunk/MESOSCALE/LMD_MM_MARS/SRC
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/LES/modif_mars/Registry.EM

    r390 r674  
    224224state  real   mars_cice       ij   misc  1  -  i012rd  "MARS_CICE"   "co2 ice"                 "kg"
    225225state  real   mars_wice       ij   misc  1  -  i012rd  "MARS_WICE"   "h2o ice"                 "kg/m2"
    226 state  real   mars_tsoil     ilj   misc  1  -  i012rd  "MARS_TSOIL"  "soil temperatures"       "K"
     226state  real   mars_tsurf      ij   misc  1  -  i012rd  "MARS_TSURF"   "surface temperature" "K"
     227state  real   mars_fluxrad    ij   misc  1  -  i012rd  "MARS_FLUXRAD" "net rad flux at surf"     "W.m-2"
     228state  real   mars_wstar      ij   misc  1  -  i012rd  "MARS_WSTAR"   "free convection velocity" "m.s-1"
     229state  real   mars_tsoil     ilj   misc  1  -  i012rd  "MARS_TSOIL"   "soil temperatures"        "K"
     230state  real   mars_q2        ikj   misc  1  Z  i012rd  "MARS_Q2"      "turbulent kinetic energy" "kg.m-3"
    227231state  real   mars_isoil     ilj   misc  1  -  i012rd  "MARS_ISOIL"  "soil thermal inertia"    "tiu"
    228232state  real   mars_dsoil     ilj   misc  1  -  i012rd  "MARS_DSOIL"  "soil depths"             "m"
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/LES/modif_mars/module_first_rk_step_part1.F

    r390 r674  
    622622     &        ,MARS_WICE=grid%mars_wice         &
    623623     &        ,MARS_TSOIL=grid%mars_tsoil                                 &
     624     &        ,MARS_Q2=grid%mars_q2                                       &
     625     &        ,MARS_FLUXRAD=grid%mars_fluxrad                             &
     626     &        ,MARS_WSTAR=grid%mars_wstar                                 &
     627     &        ,MARS_TSURF=grid%mars_tsurf                                 &
    624628#ifdef NEWPHYS
    625629     &        ,MARS_ISOIL=grid%mars_isoil       &
     
    652656#include "module_lmd_driver_output4.inc"
    653657#endif
    654      &        ,SLPX=grid%slpx,SLPY=grid%slpy)
     658     &        ,SLPX=grid%slpx,SLPY=grid%slpy,RESTART=config_flags%restart)
    655659ENDIF
    656660!!!!!!!!!!!!!!!!!!!!!!!
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/LES/modif_mars/module_initialize_les.F

    r126 r674  
    340340    grid%mars_cice(i,j)=0.
    341341    grid%mars_wice(i,j)=0.
     342!! >> Used for restarts only:
     343    grid%mars_q2(i,:,j)=0.
     344    grid%mars_fluxrad(i,j)=0.
     345    grid%mars_wstar(i,j)=0.
     346    grid%mars_tsurf(i,j)=0.
     347!! <<
    342348    grid%slpx(i,j) = 0.
    343349    grid%slpy(i,j) = 0.
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/Registry/Registry.EM

    r665 r674  
    228228####
    229229############# in module_initialize ################## in solve_em and lmd_driver ###############################
    230 state  real   albedo_gcm      ij   misc  1  -  i012rd  "MARS_ALB"    "albedo of naked ground"  "0 - 1 fraction"
    231 state  real   therm_inert     ij   misc  1  -  i012rd  "MARS_TI"     "thermal inertia"         "J/m2/K/s0.5"
    232 state  real   mars_z0         ij   misc  1  -  i012rd  "MARS_Z0"     "surface roughness"       "m"
    233 state  real   slpx            ij   misc  1  -  i012rd  "SLOPEX"      "slope x direction"       "rad"
    234 state  real   slpy            ij   misc  1  -  i012rd  "SLOPEY"      "slope y direction"       "rad"
    235 state  real   mars_emiss      ij   misc  1  -  i012rd  "MARS_EMISS"  "emissivity"              "0 - 1 fraction"
    236 state  real   mars_cice       ij   misc  1  -  i012rd  "MARS_CICE"   "co2 ice"                 "kg/m2"
    237 state  real   mars_wice       ij   misc  1  -  i012rd  "MARS_WICE"   "h2o ice"                 "kg/m2"
    238 state  real   mars_tsoil     ilj   misc  1  -  i012rd  "MARS_TSOIL"  "soil temperatures"       "K"
    239 state  real   mars_isoil     ilj   misc  1  -  i012rd  "MARS_ISOIL"  "soil thermal inertia"    "tiu"
    240 state  real   mars_dsoil     ilj   misc  1  -  i012rd  "MARS_DSOIL"  "soil depths"             "m"
    241 state  real   mars_gw        ilj   misc  1  -  i012rd  "MARS_GW"     "gwparam"                 " "
     230state  real   albedo_gcm      ij   misc  1  -  i012rd  "MARS_ALB"     "albedo of naked ground"   "0 - 1 fraction"
     231state  real   therm_inert     ij   misc  1  -  i012rd  "MARS_TI"      "thermal inertia"          "J/m2/K/s0.5"
     232state  real   mars_z0         ij   misc  1  -  i012rd  "MARS_Z0"      "surface roughness"        "m"
     233state  real   slpx            ij   misc  1  -  i012rd  "SLOPEX"       "slope x direction"        "rad"
     234state  real   slpy            ij   misc  1  -  i012rd  "SLOPEY"       "slope y direction"        "rad"
     235state  real   mars_emiss      ij   misc  1  -  i012rd  "MARS_EMISS"   "emissivity"               "0 - 1 fraction"
     236state  real   mars_cice       ij   misc  1  -  i012rd  "MARS_CICE"    "co2 ice"                  "kg/m2"
     237state  real   mars_wice       ij   misc  1  -  i012rd  "MARS_WICE"    "h2o ice"                  "kg/m2"
     238state  real   mars_fluxrad    ij   misc  1  -  i012rd  "MARS_FLUXRAD" "net rad flux at surf"     "W.m-2"
     239state  real   mars_wstar      ij   misc  1  -  i012rd  "MARS_WSTAR"   "free convection velocity" "m.s-1"
     240state  real   mars_tsurf      ij   misc  1  -  i012rd  "MARS_TSURF"   "surface temperature" "K"
     241state  real   mars_tsoil     ilj   misc  1  -  i012rd  "MARS_TSOIL"   "soil temperatures"        "K"
     242state  real   mars_q2        ikj   misc  1  Z  i012rd  "MARS_Q2"      "turbulent kinetic energy" "kg.m-3"
     243state  real   mars_isoil     ilj   misc  1  -  i012rd  "MARS_ISOIL"   "soil thermal inertia"     "tiu"
     244state  real   mars_dsoil     ilj   misc  1  -  i012rd  "MARS_DSOIL"   "soil depths"              "m"
     245state  real   mars_gw        ilj   misc  1  -  i012rd  "MARS_GW"      "gwparam"                  " "
    242246####
    243247####
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_physiq1.inc

    r234 r674  
    1414#endif
    1515               wday_ini,                      &
    16                output_tab2d, output_tab3d, flag_LES)
     16               output_tab2d, output_tab3d,    &
     17               wfluxrad,wwstar,               &
     18               flag_LES)
    1719
    1820
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_physiq2.inc

    r234 r674  
    1717#endif
    1818               wday_ini,                      &
    19                output_tab2d, output_tab3d, flag_LES)
     19               output_tab2d, output_tab3d,    &
     20               wfluxrad,wwstar,               &
     21               flag_LES)
    2022
    2123       CASE(2)
     
    2931#endif
    3032               wday_ini,                      &
    31                output_tab2d, output_tab3d, flag_LES)
     33               output_tab2d, output_tab3d,    &
     34               wfluxrad,wwstar,               &
     35               flag_LES)
    3236
    3337!       CASE(3:)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_physiq3.inc

    r234 r674  
    1717#endif
    1818               wday_ini,                      &
    19                output_tab2d, output_tab3d, flag_LES)
     19               output_tab2d, output_tab3d,    &
     20               wfluxrad,wwstar,               &
     21               flag_LES)
    2022
    2123       CASE(2)
     
    2931#endif
    3032               wday_ini,                      &
    31                output_tab2d, output_tab3d, flag_LES)
     33               output_tab2d, output_tab3d,    &
     34               wfluxrad,wwstar,               &
     35               flag_LES)
    3236
    3337       CASE(3)
     
    4145#endif
    4246               wday_ini,                      &
    43                output_tab2d, output_tab3d, flag_LES)
     47               output_tab2d, output_tab3d,    &
     48               wfluxrad,wwstar,               &
     49               flag_LES)
    4450
    4551!       CASE(3:)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_physiq4.inc

    r426 r674  
    1717#endif
    1818               wday_ini,                      &
    19                output_tab2d, output_tab3d, flag_LES)
     19               output_tab2d, output_tab3d,    &
     20               wfluxrad,wwstar,               &
     21               flag_LES)
    2022
    2123       CASE(2)
     
    2931#endif
    3032               wday_ini,                      &
    31                output_tab2d, output_tab3d, flag_LES)
     33               output_tab2d, output_tab3d,    &
     34               wfluxrad,wwstar,               &
     35               flag_LES)
    3236
    3337       CASE(3)
     
    4145#endif
    4246               wday_ini,                      &
    43                output_tab2d, output_tab3d, flag_LES)
     47               output_tab2d, output_tab3d,    &
     48               wfluxrad,wwstar,               &
     49               flag_LES)
    4450
    4551       CASE(4)
     
    5359#endif
    5460               wday_ini,                      &
    55                output_tab2d, output_tab3d, flag_LES)
    56 
     61               output_tab2d, output_tab3d,    &
     62               wfluxrad,wwstar,               &
     63               flag_LES)
    5764
    5865!       CASE(3:)
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/call_meso_physiq5.inc

    r426 r674  
    1717#endif
    1818               wday_ini,                      &
    19                output_tab2d, output_tab3d, flag_LES)
     19               output_tab2d, output_tab3d,    &
     20               wfluxrad,wwstar,               &
     21               flag_LES)
    2022
    2123       CASE(2)
     
    2931#endif
    3032               wday_ini,                      &
    31                output_tab2d, output_tab3d, flag_LES)
     33               output_tab2d, output_tab3d,    &
     34               wfluxrad,wwstar,               &
     35               flag_LES)
    3236
    3337       CASE(3)
     
    4145#endif
    4246               wday_ini,                      &
    43                output_tab2d, output_tab3d, flag_LES)
     47               output_tab2d, output_tab3d,    &
     48               wfluxrad,wwstar,               &
     49               flag_LES)
    4450
    4551       CASE(4)
     
    5359#endif
    5460               wday_ini,                      &
    55                output_tab2d, output_tab3d, flag_LES)
     61               output_tab2d, output_tab3d,    &
     62               wfluxrad,wwstar,               &
     63               flag_LES)
    5664
    5765       CASE(5)
     
    6573#endif
    6674               wday_ini,                      &
    67                output_tab2d, output_tab3d, flag_LES)
     75               output_tab2d, output_tab3d,    &
     76               wfluxrad,wwstar,               &
     77               flag_LES)
    6878
    6979
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/dyn_em/module_initialize_quarter_ss.F

    r559 r674  
    456456    grid%mars_cice(i,j)=0.
    457457    grid%mars_wice(i,j)=0.
     458!! >> Used for restarts only:
     459    grid%mars_q2(i,:,j)=0.
     460    grid%mars_fluxrad(i,j)=0.
     461    grid%mars_wstar(i,j)=0.
     462    grid%mars_tsurf(i,j)=0.
     463!! <<
    458464    write(6,*) 'NOTE TO SELF. slpx and slpy set to 0 which means no slope insolation.'
    459465    grid%slpx(i,j) = 0.
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/dyn_em/module_initialize_real.F

    r549 r674  
    278278              grid%mars_cice(i,j)=grid%st010040(i,j)
    279279              grid%mars_wice(i,j)=grid%sm100200(i,j)
     280!! >> Used for restarts only:
     281              grid%mars_q2(i,:,j)=0.
     282              grid%mars_fluxrad(i,j)=0.
     283              grid%mars_wstar(i,j)=0.
     284              grid%mars_tsurf(i,j)=0.
     285!! <<
    280286                  !! one more security ... co2ice cannot be negative
    281287                  IF (grid%mars_cice(i,j) .lt. 0.) grid%mars_cice(i,j)=0.
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/dyn_em/solve_em.F

    r488 r674  
    863863     &        ,MARS_WICE=grid%mars_wice         &
    864864     &        ,MARS_TSOIL=grid%mars_tsoil       &
     865     &        ,MARS_Q2=grid%mars_q2             &
     866     &        ,MARS_FLUXRAD=grid%mars_fluxrad   &
     867     &        ,MARS_WSTAR=grid%mars_wstar       &
     868     &        ,MARS_TSURF=grid%mars_tsurf       &
    865869#ifdef NEWPHYS
    866870     &        ,MARS_ISOIL=grid%mars_isoil       &
     
    889893#include "module_lmd_driver_output4.inc"
    890894#endif
    891      &        ,SLPX=grid%slpx,SLPY=grid%slpy)
     895     &        ,SLPX=grid%slpx,SLPY=grid%slpy,RESTART=config_flags%restart)
    892896ENDIF
    893897
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r667 r674  
    3232        MARS_WICE, &
    3333        MARS_TSOIL, &
     34        MARS_Q2, &
     35        MARS_FLUXRAD, &
     36        MARS_WSTAR, &
     37        MARS_TSURF, &
    3438#ifdef NEWPHYS
    3539        MARS_ISOIL, &
     
    5357#include "module_lmd_driver_output1.inc"
    5458#endif
    55         SLPX,SLPY)
     59        SLPX,SLPY,RESTART)
    5660! NB: module_lmd_driver_output1.inc : output arguments generated from Registry
    5761
     
    115119     MSFT,MSFU,MSFV, &
    116120     XLAT,XLONG,HT,  &
    117      MARS_ALB,MARS_TI,MARS_EMISS,MARS_CICE, &
    118      MARS_WICE, &
     121     MARS_ALB,MARS_TI,MARS_EMISS, &
    119122     SLPX,SLPY
     123REAL, DIMENSION( ims:ime, jms:jme ), INTENT(INOUT   )  :: &
     124     MARS_CICE,MARS_WICE, &
     125     MARS_FLUXRAD,MARS_WSTAR,MARS_TSURF
    120126! 3D arrays
    121127REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(IN ) :: &
    122128     dz8w,p8w,p,exner,t,t8w,rho,u,v,w,z,th
     129REAL, DIMENSION( ims:ime, kms:kme+1, jms:jme ), INTENT(INOUT ) :: &
     130     MARS_Q2
    123131!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    124132REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(INOUT ) :: &
     
    126134INTEGER, INTENT(IN   ) :: HISTORY_INTERVAL
    127135!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    128 REAL, DIMENSION( ims:ime, NUM_SOIL_LAYERS, jms:jme ), INTENT(IN  )  :: &
     136REAL, DIMENSION( ims:ime, NUM_SOIL_LAYERS, jms:jme ), INTENT(INOUT )  :: &
    129137     MARS_TSOIL
    130138#ifdef NEWPHYS
     
    141149REAL, DIMENSION( ims:ime, kms:kme, jms:jme, 1:num_3d_s ), INTENT(INOUT ) :: &
    142150     scalar
     151! Logical
     152LOGICAL, INTENT(IN ) :: restart
    143153
    144154!-------------------------------------------
     
    187197   REAL :: zmea_val,zstd_val,zsig_val,zgam_val,zthe_val
    188198   REAL :: theta_val, psi_val
     199   REAL :: wstar_val,fluxrad_val
    189200   LOGICAL :: firstcall,lastcall,tracerdyn
    190201   REAL,DIMENSION(:),ALLOCATABLE :: q2_val, qsurf_val, tsoil_val
     
    198209   REAL,DIMENSION(:),ALLOCATABLE :: wtheta, wpsi
    199210   ! v--- can they be modified ?
    200    REAL,DIMENSION(:),ALLOCATABLE :: wtsurf,wco2ice,wemis
     211   REAL,DIMENSION(:),ALLOCATABLE :: wtsurf,wco2ice,wemis,wwstar,wfluxrad
    201212   REAL,DIMENSION(:,:),ALLOCATABLE :: wq2,wqsurf,wtsoil
    202213#ifdef NEWPHYS
     
    257268#endif
    258269
     270!! FOR RESTART
     271      REAL, DIMENSION(:,:), ALLOCATABLE, SAVE :: &
     272             save_tsoil_restart
     273      REAL, DIMENSION(:), ALLOCATABLE, SAVE :: &
     274             save_tsurf_restart
     275      REAL, DIMENSION(:), ALLOCATABLE, SAVE :: &
     276             save_fluxrad_restart
     277      REAL, DIMENSION(:), ALLOCATABLE, SAVE :: &
     278             save_co2ice_restart
     279      REAL, DIMENSION(:,:), ALLOCATABLE, SAVE :: &
     280             save_q2_restart
     281      REAL, DIMENSION(:,:), ALLOCATABLE, SAVE :: &
     282             save_qsurf_restart
     283      REAL, DIMENSION(:), ALLOCATABLE, SAVE :: &
     284             save_wstar_restart
     285
    259286!!!IDEALIZED IDEALIZED
    260287      REAL :: lat_input, lon_input, ls_input, lct_input
     
    402429flag_first_restart=.false.
    403430#endif
     431
     432! Restart save arrays
     433ALLOCATE(save_tsoil_restart(ngrid,nsoil))
     434ALLOCATE(save_fluxrad_restart(ngrid))
     435ALLOCATE(save_co2ice_restart(ngrid))
     436ALLOCATE(save_q2_restart(ngrid,nlayer+1))
     437ALLOCATE(save_qsurf_restart(ngrid,nq))
     438ALLOCATE(save_wstar_restart(ngrid))
     439ALLOCATE(save_tsurf_restart(ngrid))
     440save_tsoil_restart(:,:)=0.
     441save_fluxrad_restart(:)=0.
     442save_co2ice_restart(:)=0.
     443save_q2_restart(:,:)=0.
     444save_qsurf_restart(:,:)=0.
     445save_wstar_restart(:)=0.
     446save_tsurf_restart(:)=0.
     447
    404448!! put here some general information you'd like to print just once
    405449    print *, 'TILES: ', i_start,i_end, j_start, j_end  ! numbers for simple runs, arrays for parallel runs
     
    622666ALLOCATE(wqsurf(ngrid,nq))       !!!!!
    623667ALLOCATE(wtsoil(ngrid,nsoil))    !!!!!
     668ALLOCATE(wfluxrad(ngrid))
     669ALLOCATE(wwstar(ngrid))
    624670#ifdef NEWPHYS
    625671ALLOCATE(wisoil(ngrid,nsoil))    !!!!!
     
    769815  !!! CAS DU CO2
    770816  DO iii=1,nq
    771    IF ( wtnom(iii) .eq. 'co2' ) q_prof(:,iii) = 0.95
     817   IF ( wtnom(iii) .eq. 'co2' .and. (.not. restart)) q_prof(:,iii) = 0.95
    772818  ENDDO
    773819  IF ((MARS_MODE .EQ. 20) .OR. (MARS_MODE .EQ. 21)) THEN
    774    IF (firstcall .EQV. .true.) THEN
     820   IF (firstcall .EQV. .true. .and. (.not. restart)) THEN
    775821      q_prof(:,:) = 0.95
    776822   ENDIF
     
    892938! Ground temperature, emissivity, CO2 ice cover !
    893939!-----------------------------------------------!
    894 tsurf_val=tsk(i,j)
     940IF (.not. restart) THEN
     941   tsurf_val=tsk(i,j) ! because tsk is not updated in lmd_driver, the stored value in restart is at t, not t+dt
     942                      ! note to aslmd: i dont know why we dont update tsk, so I use MARS_TSURF to be conservative
     943ELSE
     944   tsurf_val=MARS_TSURF(i,j)
     945ENDIF
    895946emis_val=MARS_EMISS(i,j)
    896947co2ice_val=MARS_CICE(i,j)
     
    912963  IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION tsoil is set to tsurf'
    913964  do k=1,nsoil
    914    tsoil_val(k) = tsurf_val
     965   IF (.not.restart) THEN
     966     tsoil_val(k) = tsurf_val
     967   ELSE
     968     !this is a restart run. We must not set tsoil to tsurf in the init.
     969     !tsoil was saved in physiq.F under the name MARS_TSOIL in the restart file
     970     !(see Registry)
     971     tsoil_val(k)=MARS_TSOIL(i,k,j)
     972   ENDIF
     973
    915974#ifdef NEWPHYS
    916975   IF ( nsoil .lt. 18 ) THEN
     
    10281087!-------------------------!
    10291088!-------------------------!
    1030 q2_val(:)=0.      !PBL wind variance
     1089IF (.not. restart) THEN
     1090   q2_val(:)=0.      !PBL wind variance
     1091   fluxrad_val=0.
     1092   wstar_val=0.
     1093ELSE
     1094   q2_val(:)=MARS_Q2(i,:,j)
     1095   fluxrad_val=MARS_FLUXRAD(i,j)
     1096   wstar_val=MARS_WSTAR(i,j)
     1097ENDIF
    10311098
    10321099!-----------------!
     
    10481115wemis(subs) = emis_val
    10491116wq2(subs,:) = q2_val(:)
     1117wfluxrad(subs) = fluxrad_val
     1118wwstar(subs) = wstar_val
    10501119wqsurf(subs,:) = qsurf_val(:)
    10511120wtsoil(subs,:) = tsoil_val(:)
     
    12061275DEALLOCATE(pw)
    12071276DEALLOCATE(pq)
    1208 DEALLOCATE(wtsurf)
    1209 DEALLOCATE(wco2ice)
     1277!DEALLOCATE(wtsurf)
     1278!DEALLOCATE(wco2ice)
    12101279DEALLOCATE(wemis)
    1211 DEALLOCATE(wq2)
    1212 DEALLOCATE(wqsurf)
    1213 DEALLOCATE(wtsoil)
     1280!DEALLOCATE(wq2)
     1281!DEALLOCATE(wqsurf)
     1282!DEALLOCATE(wtsoil)
     1283!DEALLOCATE(wwstar)
     1284!DEALLOCATE(wfluxrad)
    12141285#ifdef NEWPHYS
    12151286DEALLOCATE(wisoil)
     
    12711342dq_save(:,:,:)=pdq(:,:,:)
    12721343#endif
    1273 
     1344save_tsoil_restart(:,:)=wtsoil(:,:)
     1345save_fluxrad_restart(:)=wfluxrad(:)
     1346save_co2ice_restart(:)=wco2ice(:)
     1347save_q2_restart(:,:)=wq2(:,:)
     1348save_qsurf_restart(:,:)=wqsurf(:,:)
     1349save_wstar_restart(:)=wwstar(:)
     1350save_tsurf_restart(:)=wtsurf(:)
     1351DEALLOCATE(wtsoil)
     1352DEALLOCATE(wfluxrad)
     1353DEALLOCATE(wco2ice)
     1354DEALLOCATE(wq2)
     1355DEALLOCATE(wqsurf)
     1356DEALLOCATE(wwstar)
     1357DEALLOCATE(wtsurf)
    12741358ENDIF call_physics
    12751359
     
    13511435!---------------------------!
    13521436PSFC(i,j)=PSFC(i,j)+pdpsrf(subs)*dt    !!! here dt is needed
     1437
     1438!------------------------------------!
     1439! Save key variables for restart ! 
     1440!------------------------------------!
     1441
     1442MARS_TSOIL(i,:,j)=save_tsoil_restart(subs,:)
     1443MARS_FLUXRAD(i,j)=save_fluxrad_restart(subs)
     1444MARS_CICE(i,j)=save_co2ice_restart(subs)
     1445MARS_Q2(i,:,j)=save_q2_restart(subs,:)
     1446SELECT CASE (MARS_MODE)
     1447   CASE (1,11,12)
     1448     MARS_WICE(i,j)=save_qsurf_restart(subs,2)
     1449END SELECT
     1450MARS_WSTAR(i,j)=save_wstar_restart(subs)
     1451MARS_TSURF(i,j)=save_tsurf_restart(subs)
    13531452
    13541453!---------!
Note: See TracChangeset for help on using the changeset viewer.