Ignore:
Timestamp:
Nov 30, 2022, 11:29:29 AM (2 years ago)
Author:
romain.vande
Message:

Mars PEM:
Introduction of the possibility to follow an orbital forcing.
Introduction of new control parameters.
Cleaning of the PEM (removing unused files, add comments and new files)

A file named run_PEM.def can be added to the run.def. It contains the following variables:

_ evol_orbit_pem: Boolean. Do you want to follow an orbital forcing predefined (read in ob_ex_lsp.asc for example)? (default=false)
_ year_bp_ini: Integer. Number of year before present to start the pem run if evol_orbit_pem=.true. , default=0
_ Max_iter_pem: Integer. Maximal number of iteration if none of the stopping criterion is reached and if evol_orbit_pem=.false., default=99999999
_ dt_pem: Integer. Time step of the PEM in year, default=1
_ alpha_criterion: Real. Acceptance rate of sublimating ice surface change, default=0.2
_ soil_pem: Boolean. Do you want to run with subsurface physical processes in the PEM? default=.true.

RV

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/read_data_GCM.F90

    r2794 r2835  
    99                        nf90_inquire_dimension,nf90_close
    1010      use comsoil_h, only: nsoilmx
     11      USE soil_evolution_mod, ONLY: soil_pem
    1112
    1213      IMPLICIT NONE
     
    2324! Arguments:
    2425  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
     26  INTEGER, INTENT(IN) :: timelen                   ! number of times stored in the file
    2527
    2628  INTEGER :: iim_input,jjm_input,nlayer,nslope
     
    3436  REAL, INTENT(OUT) ::  min_co2_ice_slope(iim_input+1,jjm_input+1,nslope) ! Minimum of co2_ice slope of the year
    3537  REAL, INTENT(OUT) ::  min_h2o_ice_slope(iim_input+1,jjm_input+1,nslope) ! Minimum of co2_ice slope of the year
    36 !  REAL, ALLOCATABLE ::  vmr_co2_gcm(:,:,:)                     !!!!vmr_co2_phys_gcm(iim_input+1,jjm_input+1,timelen)
    37   REAL, INTENT(OUT) ::  vmr_co2_gcm(iim_input+1,jjm_input+1,2676)                     !!!!vmr_co2_phys_gcm(iim_input+1,jjm_input+1,timelen)
    38 !  REAL, ALLOCATABLE ::  q_h2o_GCM(:,:,:)
    39   REAL, INTENT(OUT) ::  q_h2o_GCM(iim_input+1,jjm_input+1,2676)
    40   REAL, INTENT(OUT) ::  q_co2_GCM(iim_input+1,jjm_input+1,2676)
    41 !  REAL, ALLOCATABLE ::  q_co2_GCM(:,:,:)
     38  REAL, INTENT(OUT) ::  vmr_co2_gcm(iim_input+1,jjm_input+1,timelen)      !!!!vmr_co2_phys_gcm(iim_input+1,jjm_input+1,timelen)
     39  REAL, INTENT(OUT) ::  q_h2o_GCM(iim_input+1,jjm_input+1,timelen)
     40  REAL, INTENT(OUT) ::  q_co2_GCM(iim_input+1,jjm_input+1,timelen)
    4241  REAL, ALLOCATABLE ::  q1_co2_GCM(:,:,:)
    43 !  real, INTENT(OUT) ::  vmr_co2_phys_gcm(:,:)                  !!!!vmr_co2_gcm(ngrid,timelen)
    44 !  REAL, ALLOCATABLE ::  ps_GCM(:,:,:)
    45   REAL,  INTENT(OUT) ::  ps_GCM(iim_input+1,jjm_input+1,2676)
    46 
     42  REAL,  INTENT(OUT) ::  ps_GCM(iim_input+1,jjm_input+1,timelen)
    4743
    4844!SOIL
     
    5046  REAL, INTENT(OUT) ::  tsoil_ave(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average soil temperature of the concatenated file
    5147
    52   REAL ,INTENT(OUT) ::  tsurf_gcm(iim_input+1,jjm_input+1,nslope,2676) ! Surface temperature of the concatenated file
    53   REAL , INTENT(OUT) ::  tsoil_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,2676) ! Soil temperature of the concatenated file
    54 
    55   REAL ::  TI_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,2676) ! Thermal Inertia  of the concatenated file
     48  REAL ,INTENT(OUT) ::  tsurf_gcm(iim_input+1,jjm_input+1,nslope,timelen) ! Surface temperature of the concatenated file
     49  REAL , INTENT(OUT) ::  tsoil_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Soil temperature of the concatenated file
     50
     51  REAL ::  TI_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen) ! Thermal Inertia  of the concatenated file
    5652  REAL, INTENT(OUT) ::  TI_ave(iim_input+1,jjm_input+1,nsoilmx,nslope) ! Average Thermal Inertia  of the concatenated file
    57   REAL, INTENT(OUT) ::  co2_ice_slope(iim_input+1,jjm_input+1,nslope,2676) ! Minimum of co2_ice slope of the year
     53  REAL, INTENT(OUT) ::  co2_ice_slope(iim_input+1,jjm_input+1,nslope,timelen) ! Minimum of co2_ice slope of the year
    5854!===============================================================================
    5955!   Local Variables
     
    6561
    6662  REAL,ALLOCATABLE :: time(:) ! times stored in start
    67   INTEGER :: timelen ! number of times stored in the file
    6863  INTEGER :: indextime ! index of selected time
    6964
     
    7469  INTEGER :: islope
    7570  CHARACTER*2 :: num
    76 
    7771
    7872!-----------------------------------------------------------------------
     
    8478      B=1/m_noco2
    8579
     80      allocate(co2_ice_s(iim+1,jjm+1,timelen))
     81      allocate(q1_co2_GCM(iim+1,jjm+1,timelen))
     82      allocate(h2o_ice_s_slope(iim+1,jjm+1,nslope,timelen))
     83      allocate(h2o_ice_s(iim+1,jjm+1,timelen))
     84
     85  print *, "Opening ", fichnom, "..."
     86
    8687!  Open initial state NetCDF file
    8788  var=fichnom
    8889  CALL err(NF90_OPEN(var,NF90_NOWRITE,fID),"open",var)
    8990
    90       ierr = nf90_inq_varid (fID, "temps", vID)
    91       IF (ierr .NE. nf90_noerr) THEN
    92         write(*,*)"pemetat0: Le champ <temps> est absent"
    93         write(*,*)"pemetat0: J essaie <Time>"
    94         ierr = nf90_inq_varid (fID, "Time", vID)
    95         IF (ierr .NE. nf90_noerr) THEN
    96            write(*,*)"pemetat0: Le champ <Time> est absent"
    97            write(*,*)trim(nf90_strerror(ierr))
    98      print *, "ICIIII0"
    99            CALL ABORT_gcm("pemetat0", "", 1)
    100         ENDIF
    101         ! Get the length of the "Time" dimension
    102      print *, "ICIIIITIME"
    103         ierr = nf90_inq_dimid(fID,"Time",vID)
    104         ierr = nf90_inquire_dimension(fID,vID,len=timelen)
    105       ELSE   
    106         ! Get the length of the "temps" dimension
    107      print *, "ICIIIITEMPS"
    108         ierr = nf90_inq_dimid(fID,"temps",vID)
    109         ierr = nf90_inquire_dimension(fID,vID,len=timelen)
    110       ENDIF
    111 
    112      print *, "ICIIII"
    113 
    114       allocate(co2_ice_s(iim+1,jjm+1,timelen))
    115 
    116      print *, "ICIIIIAAAA"
    117 
    118 !      allocate(q_co2_GCM(iim+1,jjm+1,timelen))
    119 
    120      print *, "ICIIIIBBBB"
    121 
    122 !      allocate(q_h2o_GCM(iim+1,jjm+1,timelen))
    123 
    124      print *, "ICIIIICCCC"
    125 
    126       allocate(q1_co2_GCM(iim+1,jjm+1,timelen))
    127 
    128      print *, "ICIIII2"
    129 
    130 
    131 
    132       allocate(h2o_ice_s_slope(iim+1,jjm+1,nslope,timelen))
    133       allocate(h2o_ice_s(iim+1,jjm+1,timelen))
    134           print *, "ICIIII3"
     91     print *, "Downloading data for h2oice ..."
    13592
    13693! Get h2o_ice_s of the concatenated file
    13794  CALL get_var3("h2o_ice_s"   ,h2o_ice_s)
    13895
    139   print *, "A"
     96     print *, "Downloading data for h2oice done"
     97     print *, "Downloading data for co2ice ..."
    14098
    14199  CALL get_var3("co2ice"   ,co2_ice_s)
     100
     101     print *, "Downloading data for co2ice done"
     102     print *, "Downloading data for vmr co2..."
     103
    142104  CALL get_var3("co2_cropped"   ,q_co2_GCM)
     105
     106     print *, "Downloading data for vmr co2 done"
     107     print *, "Downloading data for vmr h20..."
     108
    143109  CALL get_var3("h2o_cropped"   ,q_h2o_GCM)
    144110
    145   print *, "B"
     111     print *, "Downloading data for vmr h2o done"
     112     print *, "Downloading data for surface pressure ..."
    146113
    147114  CALL get_var3("ps"   ,ps_GCM)
    148115
    149   print *, "C"
    150 
    151   print *, "nslope", nslope
     116     print *, "Downloading data for surface pressure done"
     117     print *, "nslope=", nslope
     118     print *, "Downloading data for co2ice_slope ..."
    152119
    153120DO islope=1,nslope
     
    156123ENDDO
    157124
    158   print *, "co2ice_slope"
     125     print *, "Downloading data for co2ice_slope done"
     126     print *, "Downloading data for h2o_ice_s_slope ..."
    159127
    160128DO islope=1,nslope
     
    163131ENDDO
    164132
    165   print *, "h2o_ice_s_slope"
     133     print *, "Downloading data for h2o_ice_s_slope done"
     134     print *, "Downloading data for tsurf_slope ..."
    166135
    167136DO islope=1,nslope
     
    170139ENDDO
    171140
    172   print *, "tsurf_slope"
     141     print *, "Downloading data for tsurf_slope done"
     142
     143     if(soil_pem) then
     144
     145     print *, "Downloading data for tsoil_slope ..."
    173146
    174147DO islope=1,nslope
     
    177150ENDDO
    178151
    179   print *, "tsoil_slope"
     152     print *, "Downloading data for tsoil_slope done"
     153     print *, "Downloading data for inertiesoil_slope ..."
    180154
    181155DO islope=1,nslope
     
    184158ENDDO
    185159
    186   print *, "inertiesoil_slope"
    187 
    188 
    189 
    190 
     160     print *, "Downloading data for inertiesoil_slope done"
     161
     162  endif
    191163
    192164! Compute the minimum over the year for each point
     165  print *, "Computing the min of h2o_ice"
    193166  min_h2o_ice_s(:,:)=minval(h2o_ice_s,3)
     167  print *, "Computing the min of co2_ice"
    194168  min_co2_ice_s(:,:)=minval(co2_ice_s,3)
    195169
     170  print *, "Computing the min of h2o_ice_slope"
     171  min_h2o_ice_slope(:,:,:)=minval(h2o_ice_s_slope,4)
     172  print *, "Computing the min of co2_ice_slope"
    196173  min_co2_ice_slope(:,:,:)=minval(co2_ice_slope,4)
    197   min_h2o_ice_slope(:,:,:)=minval(h2o_ice_s_slope,4)
    198174
    199175!Compute averages
    200176
    201 !  DO i=1,timelen
     177    print *, "Computing average of tsurf"
    202178    tsurf_ave(:,:,:)=SUM(tsurf_gcm(:,:,:,:),4)/timelen
     179
     180  if(soil_pem) then
     181    print *, "Computing average of tsoil"
    203182    tsoil_ave(:,:,:,:)=SUM(tsoil_gcm(:,:,:,:,:),5)/timelen
     183    print *, "Computing average of TI"
    204184    TI_ave(:,:,:,:)=SUM(TI_gcm(:,:,:,:,:),5)/timelen
    205 !  ENDDO
    206 
    207 
    208 
     185  endif
    209186
    210187! By definition, a density is positive, we get rid of the negative values
     
    229206    DO j = 1, jjm+1
    230207      DO t = 1, timelen
    231 !         q1_co2_GCM(i,j,t)=q_co2_GCM(i,j,t)
    232 !         ps_GCM(i,j,t)=ps(i)
    233 !c             Mean air molecular mass = 1/(q(ico2)/m_co2 + (1-q(ico2))/m_noco2)
    234208         if (q_co2_GCM(i,j,t).LT.0) then
    235209              q_co2_GCM(i,j,t)=1E-10
     
    248222  ENDDO
    249223
    250 
    251 
    252 
    253 
    254 
    255224  CONTAINS
    256225
Note: See TracChangeset for help on using the changeset viewer.