Ignore:
Timestamp:
Feb 2, 2011, 10:14:07 PM (14 years ago)
Author:
aslmd
Message:

LMD_LES_MARS: Tests with new physics in unified frame
M 53 mesoscale/LMD_LES_MARS/modif_mars/module_model_constants.F
M 53 mesoscale/LMD_LES_MARS/modif_mars/module_first_rk_step_part1.F
M 53 mesoscale/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F
Modifications made to cope with new soil scheme

M 53 mesoscale/LMD_MM_MARS/SRC/WRFV2/mars_lmd/libf/phymars/meso_physiq.F
Commented aeronomars in old physics so that the model can compile with lots of grid points


LMD_MM_MARS: Implement tracers with the new physics. Test with JBM runs with 5 tracers

including radiatively active dust and water ice

TODO: propagate reading "traceur.def" and few initialisations from

testphys1d.F into module_lmd_driver.F

M 53 mars/libf/phymars/dimradmars.h
M 53 mars/libf/phymars/callradite.F
Change it back to both dust and ice radiatively active

M 53 mesoscale/LMD_MM_MARS/makemeso
Allow to "fresh start" with the inclusion of "clean -a" in the script

M 53 mesoscale/LMD_MM_MARS/SRC/WRFV2/Registry/Registry.EM
M 53 mesoscale/LMD_MM_MARS/SRC/WRFV2/dyn_em/module_initialize_real.F
M 53 mesoscale/LMD_MM_MARS/SRC/WRFV2/dyn_em/solve_em.F
M 53 mesoscale/LMD_MM_MARS/SRC/WRFV2/main/real_em.F
M 53 mesoscale/LMD_MM_MARS/SIMU/runmeso
Added the option mars==11 with 5 tracers: CO2 H2Ovap H2Oice DUST DUSTN
-- Note that the order matters for H2Ovap and H2Oice

LMD_MM_MARS: Create a folder to run LMD GCM with exact same physics as mesoscale

A 0 mesoscale/LMDZ.MARS/libf/phymars/physiq.F
All files in mesoscale/LMDZ.MARS/libf are links except this one
--> Because specific WRITEDIAGFI commands are set to output what is needed PREP_MARS
--> Something must be done so that qCO2, qdust, qdustN can be propagated too !!!

A 0 mesoscale/LMDZ.MARS/libf_gcm
A 0 mesoscale/LMDZ.MARS/in_lmdz_mars_newphys
Two important links that must not be broken

A 0 mesoscale/LMDZ.MARS/myGCM
This folder is for runs. Only links here -- except temp files which are not synchronized.

M 53 mesoscale/LMD_MM_MARS/SIMU/in_lmdz_mars_newphys/compile
A 0 mesoscale/LMD_MM_MARS/SIMU/in_lmdz_mars_newphys/myGCM/run.def
A 0 mesoscale/LMD_MM_MARS/SIMU/in_lmdz_mars_newphys/myGCM/traceur.def
M 53 mesoscale/LMD_MM_MARS/SIMU/in_lmdz_mars_newphys/myGCM/callphys.def
A 0 mesoscale/LMD_MM_MARS/SIMU/in_lmdz_mars_newphys/myGCM/callphys.def.csttau
Those files are needed to run the GCM in order to prepare initial & boundary

conditions for the mesoscale... but basically it is the exact same GCM

--> compile is a convenient script

A 0 mesoscale/LMDZ.MARS/makegcm
A 0 mesoscale/LMDZ.MARS/makegcm_g95
A 0 mesoscale/LMDZ.MARS/create_make_gcm
This is supposed to be merged one day with files in trunk/mars/

A 0 mesoscale/LMDZ.MARS/myGCM/DEFS_JB
Necessary files to restart a GCM run corresponding to new water cycle in JB's thesis

Location:
trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/Registry/Registry.EM

    r28 r54  
    113113state  real  QH2O_ICE  ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt) "QH2O_ICE"   "Water ice mixing ratio"     "kg kg-1"
    114114state  real  QDUST     ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt) "QDUST"      "Dust mixing ratio"          "kg kg-1"
     115####
     116state  real  Qco2        ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt)  "Qco2"         "CO2 mixing ratio"          "kg kg-1"
     117#state  real  Qdust_mass  ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt)  "Qdust_mass"   "dust_mass mixing ratio"    "kg kg-1"
     118state  real  Qdust_number  ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt)  "Qdust_number"   "dust_number mixing ratio"    "kg kg-1"
     119#state  real  Qh2o_vap  ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt)  "Qh2o_vap"   "h2o_vap mixing ratio"    "kg kg-1"
     120#state  real  Qh2o_ice  ikjftb  scalar  1  -  i01rhusdf=(bdy_interp:dt)  "Qh2o_ice"   "h2o_ice mixing ratio"    "kg kg-1"
    115121####
    116122####
     
    13241330package   nowater      mars==0                      -              moist:qv
    13251331package   water        mars==1                      -              moist:qv;scalar:qh2o,qh2o_ice
    1326 package   dust         mars==2                      -              moist:qv;scalar:qdust
     1332package   dust         mars==2                      -              moist:qv;scalar:qdust
     1333#package   newwater     mars==11                     -              scalar:qco2,qh2o,qh2o_ice
     1334package   newwater     mars==11                     -              scalar:qco2,qh2o,qh2o_ice,qdust,qdust_number
    13271335##### MARS OPTIONS
    13281336##### MARS OPTIONS
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/dyn_em/module_initialize_real.F

    r51 r54  
    12531253                            its , ite , jts , jte , kts , kte )
    12541254
    1255 if (config_flags%mars == 1) then
     1255if ( (config_flags%mars == 1) .OR. (config_flags%mars == 11) ) then
    12561256!if (size(scalar(0,0,0,:)) > 2) then
    12571257!! autre possibilite: activer les flags dans metgrid.tbl
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/dyn_em/solve_em.F

    r34 r54  
    26922692
    26932693!!!!****MARS: pass water vapor at boundaries (and all other tracers if nested domains)
    2694 IF ( ( (config_flags%mars .eq. 1) .AND. (is .EQ. 2) ) .OR. config_flags%nested ) THEN
     2694IF (  ( (config_flags%mars .eq. 1) .AND. (is .EQ. 2) ) &
     2695 .OR. ( (config_flags%mars .eq. 11) .AND. (is .EQ. 2) ) &
     2696 .OR. config_flags%nested ) THEN
    26952697         CALL relax_bdy_scalar ( scalar_tend(ims,kms,jms,is),            &
    26962698                                 scalar(ims,kms,jms,is),  grid%em_mut,         &
     
    27502752!!!!****MARS: if parent domain and any other tracer than water vapor, no bdy and simple zero flux bdy condition
    27512753IF (  config_flags%specified  ) THEN
    2752 IF ( (config_flags%mars .ne. 1) .OR. ((config_flags%mars .eq. 1) .and. (is .ne. 2)) ) THEN
     2754IF (    (config_flags%mars .ne. 1) &
     2755   .OR. ((config_flags%mars .eq. 11) .and. (is .ne. 2)) &
     2756   .OR. ((config_flags%mars .eq. 1 ) .and. (is .ne. 2)) ) THEN
    27532757           CALL flow_dep_bdy  ( scalar(ims,kms,jms,is),     &
    27542758                                grid%em_ru_m, grid%em_rv_m, config_flags,   &
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/main/real_em.F

    r11 r54  
    679679!                    ids, ide, jds, jde, kds, kde, ims, ime, jms, jme, kms, kme, ips, ipe, jps, jpe, kps, kpe )
    680680!!!!MARS : pb a regler avec P_QH2O qui n est pas reconnu si QH2O n est pas dans active dans le registry
    681 IF ( config_flags%mars .eq. 1 ) THEN
     681IF ( (config_flags%mars .eq. 1) .OR. (config_flags%mars == 11) ) THEN
    682682      CALL couple ( grid%em_mu_2 , grid%em_mub , qbdy3dtemp1 , grid%scalar(:,:,:,2) , 't' , grid%msft , &
    683683                    ids, ide, jds, jde, kds, kde, ims, ime, jms, jme, kms, kme, ips, ipe, jps, jpe, kps, kpe )
     
    742742!                                                                 ips , ipe , jps , jpe , kps , kpe )
    743743!!!!MARS
    744 IF ( config_flags%mars .eq. 1 ) THEN
     744IF ( (config_flags%mars .eq. 1) .OR. (config_flags%mars == 11) ) THEN
    745745      CALL stuff_bdy     ( qbdy3dtemp1 , grid%scalar_b(:,:,:,:,2)   , 'T' , ijds , ijde , spec_bdy_width      , &
    746746                                                                 ids , ide , jds , jde , kds , kde , &
     
    808808!                    ids, ide, jds, jde, kds, kde, ims, ime, jms, jme, kms, kme, ips, ipe, jps, jpe, kps, kpe )
    809809!!!!MARS
    810 IF ( config_flags%mars .eq. 1 ) THEN
     810IF ( (config_flags%mars .eq. 1) .OR. (config_flags%mars == 11) ) THEN
    811811      CALL couple ( grid%em_mu_2 , grid%em_mub , qbdy3dtemp2 , grid%scalar(:,:,:,2) , 't' , grid%msft , &
    812812                    ids, ide, jds, jde, kds, kde, ims, ime, jms, jme, kms, kme, ips, ipe, jps, jpe, kps, kpe )
     
    874874!                                                            ips , ipe , jps , jpe , kps , kpe )
    875875!!!!MARS
    876 IF ( config_flags%mars .eq. 1 ) THEN
     876IF ( (config_flags%mars .eq. 1) .OR. (config_flags%mars == 11) ) THEN
    877877      CALL stuff_bdytend ( qbdy3dtemp2 , qbdy3dtemp1 , REAL(interval_seconds) , grid%scalar_bt(:,:,:,:,2) , 'T' , &
    878878                                                            ijds , ijde , spec_bdy_width      , &
     
    10281028!                                                                    ips , ipe , jps , jpe , kps , kpe )
    10291029!!!!MARS
    1030 IF ( config_flags%mars .eq. 1 ) THEN
     1030IF ( (config_flags%mars .eq. 1) .OR. (config_flags%mars == 11) ) THEN
    10311031        CALL stuff_bdy     ( qbdy3dtemp1 , grid%scalar_b(:,:,:,:,2)   , 'T', ijds , ijde , spec_bdy_width      , &
    10321032                                                                    ids , ide , jds , jde , kds , kde , &
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/mars_lmd/libf/phymars/meso_physiq.F

    r11 r54  
    873873
    874874
    875 c-----------------------------------------------------------------------
    876 c    3. Gravity wave and subgrid scale topography drag :
    877 c    -------------------------------------------------
    878 
    879 
    880       IF(calllott)THEN
    881 
    882         CALL calldrag_noro(ngrid,nlayer,ptimestep,
    883      &                 pplay,pplev,pt,pu,pv,zdtgw,zdugw,zdvgw)
    884 
    885         DO l=1,nlayer
    886           DO ig=1,ngrid
    887             pdv(ig,l)=pdv(ig,l)+zdvgw(ig,l)
    888             pdu(ig,l)=pdu(ig,l)+zdugw(ig,l)
    889             pdt(ig,l)=pdt(ig,l)+zdtgw(ig,l)
    890           ENDDO
    891         ENDDO
    892       ENDIF
     875!c-----------------------------------------------------------------------
     876!c    3. Gravity wave and subgrid scale topography drag :
     877!c    -------------------------------------------------
     878!
     879!
     880!      IF(calllott)THEN
     881!
     882!        CALL calldrag_noro(ngrid,nlayer,ptimestep,
     883!     &                 pplay,pplev,pt,pu,pv,zdtgw,zdugw,zdvgw)
     884!
     885!        DO l=1,nlayer
     886!          DO ig=1,ngrid
     887!            pdv(ig,l)=pdv(ig,l)+zdvgw(ig,l)
     888!            pdu(ig,l)=pdu(ig,l)+zdugw(ig,l)
     889!            pdt(ig,l)=pdt(ig,l)+zdtgw(ig,l)
     890!          ENDDO
     891!        ENDDO
     892!      ENDIF
    893893
    894894c-----------------------------------------------------------------------
     
    11531153c     ------------------
    11541154
    1155 c        --------------
    1156 c        photochemistry :
    1157 c        --------------
    1158          IF(photochem .or. thermochem) then
    1159           call calchim(ptimestep,pplay,pplev,pt,pdt,dist_sol,mu0,
    1160      .      zzlay,zday,pq,pdq,zdqchim,zdqschim,zdqcloud,zdqscloud)
    1161            
    1162 c Photochemistry includes condensation of H2O2
    1163 
    1164            do iq=nqchem_min,nq
    1165             if (noms(iq).eq."h2o2") then
    1166              DO l=1,nlayer
    1167                DO ig=1,ngrid
    1168                     pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqchim(ig,l,iq)
    1169                     pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqcloud(ig,l,iq)
    1170                ENDDO
    1171              ENDDO
    1172             else
    1173              DO l=1,nlayer
    1174                DO ig=1,ngrid
    1175                     pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqchim(ig,l,iq)
    1176                ENDDO
    1177              ENDDO
    1178             endif
    1179            ENDDO
    1180            do iq=nqchem_min,nq
    1181             if (noms(iq).eq."h2o2") then
    1182                DO ig=1,ngrid
    1183                     dqsurf(ig,iq)= dqsurf(ig,iq) + zdqschim(ig,iq)
    1184                     dqsurf(ig,iq)= dqsurf(ig,iq) + zdqscloud(ig,iq)
    1185                ENDDO
    1186             else
    1187                DO ig=1,ngrid
    1188                     dqsurf(ig,iq)= dqsurf(ig,iq) + zdqschim(ig,iq)
    1189                ENDDO
    1190             endif
    1191            ENDDO
    1192 
    1193          END IF  ! (photochem.or.thermochem)
    1194 c        print*,'photochem ok'
     1155!c        --------------
     1156!c        photochemistry :
     1157!c        --------------
     1158!         IF(photochem .or. thermochem) then
     1159!          call calchim(ptimestep,pplay,pplev,pt,pdt,dist_sol,mu0,
     1160!     .      zzlay,zday,pq,pdq,zdqchim,zdqschim,zdqcloud,zdqscloud)
     1161!           
     1162!c Photochemistry includes condensation of H2O2
     1163!
     1164!           do iq=nqchem_min,nq
     1165!            if (noms(iq).eq."h2o2") then
     1166!             DO l=1,nlayer
     1167!               DO ig=1,ngrid
     1168!                    pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqchim(ig,l,iq)
     1169!                    pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqcloud(ig,l,iq)
     1170!               ENDDO
     1171!             ENDDO
     1172!            else
     1173!             DO l=1,nlayer
     1174!               DO ig=1,ngrid
     1175!                    pdq(ig,l,iq)=pdq(ig,l,iq)+ zdqchim(ig,l,iq)
     1176!               ENDDO
     1177!             ENDDO
     1178!            endif
     1179!           ENDDO
     1180!           do iq=nqchem_min,nq
     1181!            if (noms(iq).eq."h2o2") then
     1182!               DO ig=1,ngrid
     1183!                    dqsurf(ig,iq)= dqsurf(ig,iq) + zdqschim(ig,iq)
     1184!                    dqsurf(ig,iq)= dqsurf(ig,iq) + zdqscloud(ig,iq)
     1185!               ENDDO
     1186!            else
     1187!               DO ig=1,ngrid
     1188!                    dqsurf(ig,iq)= dqsurf(ig,iq) + zdqschim(ig,iq)
     1189!               ENDDO
     1190!            endif
     1191!           ENDDO
     1192!
     1193!         END IF  ! (photochem.or.thermochem)
     1194!c        print*,'photochem ok'
    11951195
    11961196c   7c. Aerosol particles
     
    12741274
    12751275
    1276 c-----------------------------------------------------------------------
    1277 c   8.5 THERMOSPHERE CALCULATION
    1278 c-----------------------------------------------------------------------
    1279 
    1280       if (callthermos) then
    1281         call thermosphere(pplev,pplay,dist_sol,
    1282      $     mu0,ptimestep,ptime,zday,tsurf,zzlev,zzlay,
    1283      &     pt,pq,pu,pv,pdt,pdq,
    1284      $     zdteuv,zdtconduc,zdumolvis,zdvmolvis,zdqmoldiff)
    1285 c           do iq=nqchem_min,nq
    1286 c           write(*,*) 'thermo iq,pq',iq,pq(690,1,iq)
    1287 c           enddo
    1288 
    1289         DO l=1,nlayer
    1290           DO ig=1,ngrid
    1291             dtrad(ig,l)=dtrad(ig,l)+zdteuv(ig,l)
    1292             pdt(ig,l)=pdt(ig,l)+zdtconduc(ig,l)
    1293      &                         +zdteuv(ig,l)
    1294             pdv(ig,l)=pdv(ig,l)+zdvmolvis(ig,l)
    1295             pdu(ig,l)=pdu(ig,l)+zdumolvis(ig,l)
    1296             DO iq=1, nq
    1297               pdq(ig,l,iq)=pdq(ig,l,iq)+zdqmoldiff(ig,l,iq)
    1298             ENDDO
    1299           ENDDO
    1300         ENDDO
    1301 
    1302 
    1303       endif
     1276!c-----------------------------------------------------------------------
     1277!c   8.5 THERMOSPHERE CALCULATION
     1278!c-----------------------------------------------------------------------
     1279!
     1280!      if (callthermos) then
     1281!        call thermosphere(pplev,pplay,dist_sol,
     1282!     $     mu0,ptimestep,ptime,zday,tsurf,zzlev,zzlay,
     1283!     &     pt,pq,pu,pv,pdt,pdq,
     1284!     $     zdteuv,zdtconduc,zdumolvis,zdvmolvis,zdqmoldiff)
     1285!c           do iq=nqchem_min,nq
     1286!c           write(*,*) 'thermo iq,pq',iq,pq(690,1,iq)
     1287!c           enddo
     1288!
     1289!        DO l=1,nlayer
     1290!          DO ig=1,ngrid
     1291!            dtrad(ig,l)=dtrad(ig,l)+zdteuv(ig,l)
     1292!            pdt(ig,l)=pdt(ig,l)+zdtconduc(ig,l)
     1293!     &                         +zdteuv(ig,l)
     1294!            pdv(ig,l)=pdv(ig,l)+zdvmolvis(ig,l)
     1295!            pdu(ig,l)=pdu(ig,l)+zdumolvis(ig,l)
     1296!            DO iq=1, nq
     1297!              pdq(ig,l,iq)=pdq(ig,l,iq)+zdqmoldiff(ig,l,iq)
     1298!            ENDDO
     1299!          ENDDO
     1300!        ENDDO
     1301!
     1302!
     1303!      endif
     1304
    13041305c-----------------------------------------------------------------------
    13051306c   8. Surface  and sub-surface soil temperature
  • trunk/mesoscale/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r34 r54  
    697697   tsoil_val = tsoil_val*0. + tsurf_val
    698698  ENDIF
     699#ifdef NEWPHYS
     700  isoil_val(:)=MARS_ISOIL(i,:,j)
     701  dsoil_val(:)=MARS_DSOIL(i,:,j)
     702#endif
    699703ELSE
    700704  IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION tsoil is set to tsurf'
    701705  do k=1,nsoil
    702706   tsoil_val(k) = tsurf_val
     707#ifdef NEWPHYS
     708   IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** IDEALIZED SIMULATION isoil and dsoil standard'
     709   isoil_val(k) = inertiedat_val
     710   dsoil_val(k) = sqrt(887.75/3.14)*((2.**(k-0.5))-1.) * inertiedat_val / wvolcapa
     711   IF ( (i == ips) .AND. (j == jps) ) PRINT *,'** Mars ** ISOIL DSOIL are ',isoil_val(k), dsoil_val(k)
     712#endif
    703713  enddo
    704714ENDIF
    705 
    706 #ifdef NEWPHYS
    707 isoil_val(:)=MARS_ISOIL(i,:,j)
    708 dsoil_val(:)=MARS_DSOIL(i,:,j)
    709 #endif
    710715
    711716!-------------------!
Note: See TracChangeset for help on using the changeset viewer.