Changeset 324 for trunk/MESOSCALE


Ignore:
Timestamp:
Oct 21, 2011, 11:31:28 AM (13 years ago)
Author:
aslmd
Message:

MESOSCALE : Preparatory commit for the ultimate option mars=42 which

would allow mesoscale modeling with photochemistry.

[see r76 method to add 'mars' options]
Modified module_lmd_driver.F and Registry.EM and runmeso
Modified readmeteo.F90 and introduced an option -DPHOTOCHEM
...
Transparent to the casual user
Option mars=42 not yet finished though -- so do not use!

Location:
trunk/MESOSCALE/LMD_MM_MARS
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SIMU/runmeso

    r279 r324  
    178178      3) tracers='2' ;;
    179179     11) tracers='4' ;;
     180     42) tracers='18' ;;
    180181      *) tracers='1' ;;
    181182  esac
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/compile_pgf

    r235 r324  
    88-L$NETCDF/lib -lnetcdf \
    99-I$NETCDF/include \
    10 -o readmeteo.exe
     10-o readmeteo.exe #-DPHOTOCHEM
    1111
    1212pgf90 create_readmeteo.F90 \
    1313-L$NETCDF/lib -lnetcdf \
    1414-I$NETCDF/include \
    15 -o create_readmeteo.exe
     15-o create_readmeteo.exe #-DPHOTOCHEM \
    1616
    1717\rm fix_no_info.inc 2> /dev/null
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/readmeteo.F90

    r73 r324  
    9898character*13, dimension(:), allocatable :: date_out
    9999character*19, dimension(:), allocatable :: date_out2
     100
     101#ifdef PHOTOCHEM
     102real, dimension(:,:,:,:,:), allocatable :: chemtrac
     103integer :: nchemtrac,i
     104CHARACTER*20,DIMENSION(:),ALLOCATABLE :: wtnom
     105#endif
     106
     107
    100108!***************************************************************************
    101109!***************************************************************************
     
    230238allocate(interm(lonlen,latlen))
    231239allocate(gwparam(lonlen,latlen,5))
    232 allocate(ghtsfile(lonlen,latlen))       !! no scan axis
     240allocate(ghtsfile(lonlen,latlen))    !! no scan axis
    233241allocate(vide(lonlen,latlen))
    234242allocate(ones(lonlen,latlen))
    235243allocate(lat(latlen), lon(lonlen), alt(altlen), time(timelen))
    236244allocate(aps(altlen),bps(altlen),levels(altlen))
     245#ifdef PHOTOCHEM
     246nchemtrac = 14
     247allocate(wtnom(nchemtrac))
     248wtnom(1)  = "c_co2"
     249wtnom(2)  = "c_co"
     250wtnom(3)  = "c_o"
     251wtnom(4)  = "c_o1d"
     252wtnom(5)  = "c_o2"
     253wtnom(6)  = "c_o3"
     254wtnom(7)  = "c_h"
     255wtnom(8)  = "c_h2"
     256wtnom(9)  = "c_oh"
     257wtnom(10) = "c_ho2"
     258wtnom(11) = "c_h2o2"
     259wtnom(12) = "c_ch4"
     260wtnom(13) = "c_n2"
     261wtnom(14) = "c_ar"
     262allocate(chemtrac(lonlen,latlen,altlen,timelen,nchemtrac))
     263chemtrac(:,:,:,:,:)=0
     264#endif
    237265
    238266tfile(:,:,:,:)=0
     
    523551   IF (ierr .NE. NF_NOERR) THEN
    524552      ierr = NF_INQ_VARID (nid,"t",nvarid)
    525         IF (ierr .NE. NF_NOERR) THEN
     553        IF (ierr .NE. NF_NOERR) THEN
    526554          PRINT *, "Error: Readmeteo <t> not found"
    527555          stop
    528         ENDIF
     556        ENDIF
    529557   ENDIF
    530558#ifdef NC_DOUBLE
     
    627655!! special dust stuff
    628656!!------------------------
    629 
    630657
    631658!SELECT CASE(ident)
     
    677704!!!!!!!!
    678705!!!!!!!! new physics
     706
     707
     708!!!!!!!!!!!!!!!!!!!!!!!!NEW PHYSICS + PHOTOCHEM
     709!!!!!!!!!!!!!!!!!!!!!!!!NEW PHYSICS + PHOTOCHEM
     710#ifdef PHOTOCHEM
     711    print *,'photochem'
     712    DO i=1,nchemtrac
     713     print *,wtnom(i)
     714     ierr=NF_INQ_VARID(nid,wtnom(i),nvarid)
     715     if (ierr.ne.NF_NOERR) then
     716       write(*,*) "...No ",wtnom(i), " - set to 0"
     717       chemtrac(:,:,:,:,i)=0.
     718     else
     719       ierr=NF_GET_VAR_REAL(nid,nvarid,chemtrac(:,:,:,:,i))
     720     endif
     721    ENDDO
     722#endif
     723!!!!!!!!!!!!!!!!!!!!!!!!NEW PHYSICS + PHOTOCHEM
     724!!!!!!!!!!!!!!!!!!!!!!!!NEW PHYSICS + PHOTOCHEM
     725
    679726
    680727
     
    11921239!print *,'The field '//DESC//' was written to '//output
    11931240
     1241!------------------------!
     1242! >>> Write a variable   !
     1243!     PHOTOCHEMISTRY     !
     1244!------------------------!
     1245#ifdef PHOTOCHEM
     1246    DO i=1,nchemtrac
     1247       FIELD=wtnom(i)
     1248       UNITS='units'
     1249       DESC='desc'
     1250       XLVL=200100.
     1251       SLAB=chemtrac(:,:,1,time_out(l),i)
     1252       ! And now put everything in the destination file
     1253       ! ... Header
     1254       write(1) IFV
     1255       write(1) HDATE,XFCST,SOURCE,FIELD,UNITS,DESC,XLVL,NX,NY,IPROJ
     1256       write(1) STARTLOC,STARTLAT,STARTLON,DELTALAT,DELTALON
     1257       ! ... Data
     1258       write(1) SLAB
     1259    ENDDO
     1260#endif
    11941261
    11951262!!----------------------------------------------------
     
    14551522END DO
    14561523!print *,'The field '//DESC//' was written to '//output
     1524
     1525
     1526!------------------------!
     1527! >>> Write a variable   !
     1528!     PHOTOCHEMISTRY     !
     1529!------------------------!
     1530#ifdef PHOTOCHEM
     1531    DO i=1,nchemtrac
     1532       FIELD=wtnom(i)
     1533       UNITS='units'
     1534       DESC='desc'
     1535       DO k = 1,altlen
     1536         XLVL=levels(k)
     1537         SLAB=chemtrac(:,:,k,time_out(l),i)
     1538         ! And now put everything in the destination file
     1539         ! ... Header
     1540         write(1) IFV
     1541         write(1) HDATE,XFCST,SOURCE,FIELD,UNITS,DESC,XLVL,NX,NY,IPROJ
     1542         write(1) STARTLOC,STARTLAT,STARTLON,DELTALAT,DELTALON
     1543         ! ... Data
     1544         write(1) SLAB
     1545       END DO
     1546    ENDDO
     1547#endif
    14571548
    14581549print *,'****done file '//output, int(100.*float(l)/float(FILES)), ' % '
     
    14981589deallocate(aps,bps,levels)
    14991590
     1591#ifdef PHOTOCHEM
     1592deallocate(chemtrac)
     1593deallocate(wtnom)
     1594#endif
    15001595
    15011596print *, '------------------------'
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/Registry/Registry.EM

    r316 r324  
    130130state  real  qdustn    ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "QDUSTN"        "Dust_number mixing ratio"   "kg kg-1"
    131131state  real  qco2      ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "QCO2"          "CO2 mixing ratio"           "kg kg-1"
     132state  real  chem_co   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_co"     ""   ""
     133state  real  chem_o    ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_o"      ""   ""
     134state  real  chem_o1d  ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_o1d"    ""   ""
     135state  real  chem_o2   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_o2"     ""   ""
     136state  real  chem_o3   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_o3"     ""   ""
     137state  real  chem_h    ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_h"      ""   ""
     138state  real  chem_h2   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_h2"     ""   ""
     139state  real  chem_oh   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_oh"     ""   ""
     140state  real  chem_ho2  ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_ho2"    ""   ""
     141state  real  chem_h2o2 ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_h2o2"   ""   ""
     142state  real  chem_ch4  ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_ch4"    ""   ""
     143state  real  chem_n2   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_n2"     ""   ""
     144state  real  chem_ar   ikjftb  scalar  1  -  i01rusdf=(bdy_interp:dt)  "chem_ar"     ""   ""
    132145####
    133146####
     
    13531366package   dust2eq      mars==3                      -              scalar:qdust,qdustn
    13541367package   newwater     mars==11                     -              scalar:qh2o,qh2o_ice,qdust,qdustn
     1368package   photochem    mars==42                     -              scalar:qco2,chem_co,chem_o,chem_o1d,chem_o2,chem_o3,chem_h,chem_h2,chem_oh,chem_ho2,chem_h2o2,chem_ch4,chem_n2,chem_ar,qh2o_ice,qh2o,qdust,qdustn
    13551369##### MARS OPTIONS
    13561370##### MARS OPTIONS
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F

    r315 r324  
    650650
    651651SELECT CASE (MARS_MODE) !! ONLY ALLOW FOR MODES DEFINED IN Registry.EM
    652    CASE(4-10,12-19,22:)      !! -- CHANGE THIS if YOU ADDED CASES in REGISTRY.EM
     652   CASE(4-10,12-19,22-41,43:)      !! -- CHANGE THIS if YOU ADDED CASES in REGISTRY.EM
    653653   PRINT *, 'NOT SUPPORTED, to be done'
    654654   STOP
     
    662662!package   radioac      mars==20                     -              scalar:qtrac1
    663663!package   radioac2     mars==21                     -              scalar:upward,downward
     664!package   photochem    mars==42                     -              scalar:qco2,chem_co,chem_o,chem_o1d,chem_o2,chem_o3,chem_h,chem_h2,chem_oh,chem_ho2,chem_h2o2,chem_ch4,chem_n2,chem_ar,qh2o_ice,qh2o,qdust,qdustn
    664665!!!!!!!!!!!!!!!!!!! FOR REFERENCE
    665666
     
    672673      wtnom(nq) = 'co2'
    673674    CASE(1)
    674       wtnom(1)  = 'h2o_vap'     
    675       wtnom(2)  = 'h2o_ice'    
     675      wtnom(1)  = 'h2o_vap'
     676      wtnom(2)  = 'h2o_ice'
    676677    CASE(2)
    677678      wtnom(1)  = 'dust01'     
    678679    CASE(3)
    679680      wtnom(1)  = 'dust_mass'
    680       wtnom(2)  = 'dust_number'
     681      wtnom(2)  = 'dust_number' 
    681682    CASE(11)
    682683      wtnom(1)  = 'h2o_vap'
    683       wtnom(2)  = 'h2o_ice'
     684      wtnom(2)  = 'h2o_ice' 
    684685      wtnom(3)  = 'dust_mass'
    685686      wtnom(4)  = 'dust_number'
     
    688689    CASE(21)
    689690      wtnom(1) = 'upward'
    690       wtnom(2) = 'downward'
     691      wtnom(2) = 'downward'
     692    CASE(42)
     693      wtnom(1)  = 'co2'
     694      wtnom(2)  = 'co'
     695      wtnom(3)  = 'o'
     696      wtnom(4)  = 'o1d'
     697      wtnom(5)  = 'o2'
     698      wtnom(6)  = 'o3'
     699      wtnom(7)  = 'h'
     700      wtnom(8)  = 'h2'
     701      wtnom(9)  = 'oh'
     702      wtnom(10)  = 'ho2'
     703      wtnom(11)  = 'h2o2'
     704      wtnom(12)  = 'ch4'
     705      wtnom(13)  = 'n2'
     706      wtnom(14)  = 'ar'
     707      wtnom(15)  = 'h2o_ice'
     708      wtnom(16)  = 'h2o_vap'
     709      wtnom(17)  = 'dust_mass'
     710      wtnom(18)  = 'dust_number'
    691711END SELECT
    692712#endif
     
    729749q_prof(:,1:nq) = SCALAR(i,kps:kpe,j,2:nq+1)  !! the names were set above !! one dummy tracer in WRF
    730750  !!! CAS DU CO2
    731 DO iii=1,nq
    732  IF ( wtnom(iii) .eq. 'co2' ) q_prof(:,iii) = 0.95
    733 ENDDO
    734 
    735 IF ((MARS_MODE .EQ. 20) .OR. (MARS_MODE .EQ. 21)) THEN
     751  DO iii=1,nq
     752   IF ( wtnom(iii) .eq. 'co2' ) q_prof(:,iii) = 0.95
     753  ENDDO
     754  IF ((MARS_MODE .EQ. 20) .OR. (MARS_MODE .EQ. 21)) THEN
    736755   IF (firstcall .EQV. .true.) THEN
    737756      q_prof(:,:) = 0.95
    738757   ENDIF
    739 ENDIF
    740 
     758  ENDIF
    741759#else
    742760SELECT CASE (MARS_MODE)
     
    841859!!!! ADDITIONAL SECURITY. THIS MIGHT HAPPEN WITH OLD INIT FILES.
    842860IF (z0_val == 0.) THEN
    843    PRINT *, 'WELL, z0 is 0, this is no good. Setting to old defaults value 0.01 m'
     861   IF ( (i == ips) .AND. (j == jps) ) PRINT *, 'WELL, z0 is 0, this is no good. Setting to old defaults value 0.01 m'
    844862   z0_val = 0.01
    845863ENDIF
Note: See TracChangeset for help on using the changeset viewer.