Changeset 324 for trunk/MESOSCALE
- Timestamp:
- Oct 21, 2011, 11:31:28 AM (13 years ago)
- Location:
- trunk/MESOSCALE/LMD_MM_MARS
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/MESOSCALE/LMD_MM_MARS/SIMU/runmeso
r279 r324 178 178 3) tracers='2' ;; 179 179 11) tracers='4' ;; 180 42) tracers='18' ;; 180 181 *) tracers='1' ;; 181 182 esac -
trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/compile_pgf
r235 r324 8 8 -L$NETCDF/lib -lnetcdf \ 9 9 -I$NETCDF/include \ 10 -o readmeteo.exe 10 -o readmeteo.exe #-DPHOTOCHEM 11 11 12 12 pgf90 create_readmeteo.F90 \ 13 13 -L$NETCDF/lib -lnetcdf \ 14 14 -I$NETCDF/include \ 15 -o create_readmeteo.exe 15 -o create_readmeteo.exe #-DPHOTOCHEM \ 16 16 17 17 \rm fix_no_info.inc 2> /dev/null -
trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/readmeteo.F90
r73 r324 98 98 character*13, dimension(:), allocatable :: date_out 99 99 character*19, dimension(:), allocatable :: date_out2 100 101 #ifdef PHOTOCHEM 102 real, dimension(:,:,:,:,:), allocatable :: chemtrac 103 integer :: nchemtrac,i 104 CHARACTER*20,DIMENSION(:),ALLOCATABLE :: wtnom 105 #endif 106 107 100 108 !*************************************************************************** 101 109 !*************************************************************************** … … 230 238 allocate(interm(lonlen,latlen)) 231 239 allocate(gwparam(lonlen,latlen,5)) 232 allocate(ghtsfile(lonlen,latlen)) 240 allocate(ghtsfile(lonlen,latlen)) !! no scan axis 233 241 allocate(vide(lonlen,latlen)) 234 242 allocate(ones(lonlen,latlen)) 235 243 allocate(lat(latlen), lon(lonlen), alt(altlen), time(timelen)) 236 244 allocate(aps(altlen),bps(altlen),levels(altlen)) 245 #ifdef PHOTOCHEM 246 nchemtrac = 14 247 allocate(wtnom(nchemtrac)) 248 wtnom(1) = "c_co2" 249 wtnom(2) = "c_co" 250 wtnom(3) = "c_o" 251 wtnom(4) = "c_o1d" 252 wtnom(5) = "c_o2" 253 wtnom(6) = "c_o3" 254 wtnom(7) = "c_h" 255 wtnom(8) = "c_h2" 256 wtnom(9) = "c_oh" 257 wtnom(10) = "c_ho2" 258 wtnom(11) = "c_h2o2" 259 wtnom(12) = "c_ch4" 260 wtnom(13) = "c_n2" 261 wtnom(14) = "c_ar" 262 allocate(chemtrac(lonlen,latlen,altlen,timelen,nchemtrac)) 263 chemtrac(:,:,:,:,:)=0 264 #endif 237 265 238 266 tfile(:,:,:,:)=0 … … 523 551 IF (ierr .NE. NF_NOERR) THEN 524 552 ierr = NF_INQ_VARID (nid,"t",nvarid) 525 553 IF (ierr .NE. NF_NOERR) THEN 526 554 PRINT *, "Error: Readmeteo <t> not found" 527 555 stop 528 556 ENDIF 529 557 ENDIF 530 558 #ifdef NC_DOUBLE … … 627 655 !! special dust stuff 628 656 !!------------------------ 629 630 657 631 658 !SELECT CASE(ident) … … 677 704 !!!!!!!! 678 705 !!!!!!!! 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 679 726 680 727 … … 1192 1239 !print *,'The field '//DESC//' was written to '//output 1193 1240 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 1194 1261 1195 1262 !!---------------------------------------------------- … … 1455 1522 END DO 1456 1523 !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 1457 1548 1458 1549 print *,'****done file '//output, int(100.*float(l)/float(FILES)), ' % ' … … 1498 1589 deallocate(aps,bps,levels) 1499 1590 1591 #ifdef PHOTOCHEM 1592 deallocate(chemtrac) 1593 deallocate(wtnom) 1594 #endif 1500 1595 1501 1596 print *, '------------------------' -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/Registry/Registry.EM
r316 r324 130 130 state real qdustn ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "QDUSTN" "Dust_number mixing ratio" "kg kg-1" 131 131 state real qco2 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "QCO2" "CO2 mixing ratio" "kg kg-1" 132 state real chem_co ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_co" "" "" 133 state real chem_o ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_o" "" "" 134 state real chem_o1d ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_o1d" "" "" 135 state real chem_o2 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_o2" "" "" 136 state real chem_o3 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_o3" "" "" 137 state real chem_h ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_h" "" "" 138 state real chem_h2 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_h2" "" "" 139 state real chem_oh ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_oh" "" "" 140 state real chem_ho2 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_ho2" "" "" 141 state real chem_h2o2 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_h2o2" "" "" 142 state real chem_ch4 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_ch4" "" "" 143 state real chem_n2 ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_n2" "" "" 144 state real chem_ar ikjftb scalar 1 - i01rusdf=(bdy_interp:dt) "chem_ar" "" "" 132 145 #### 133 146 #### … … 1353 1366 package dust2eq mars==3 - scalar:qdust,qdustn 1354 1367 package newwater mars==11 - scalar:qh2o,qh2o_ice,qdust,qdustn 1368 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 1355 1369 ##### MARS OPTIONS 1356 1370 ##### MARS OPTIONS -
trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/phys/module_lmd_driver.F
r315 r324 650 650 651 651 SELECT 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.EM652 CASE(4-10,12-19,22-41,43:) !! -- CHANGE THIS if YOU ADDED CASES in REGISTRY.EM 653 653 PRINT *, 'NOT SUPPORTED, to be done' 654 654 STOP … … 662 662 !package radioac mars==20 - scalar:qtrac1 663 663 !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 664 665 !!!!!!!!!!!!!!!!!!! FOR REFERENCE 665 666 … … 672 673 wtnom(nq) = 'co2' 673 674 CASE(1) 674 wtnom(1) = 'h2o_vap' 675 wtnom(2) = 'h2o_ice' 675 wtnom(1) = 'h2o_vap' 676 wtnom(2) = 'h2o_ice' 676 677 CASE(2) 677 678 wtnom(1) = 'dust01' 678 679 CASE(3) 679 680 wtnom(1) = 'dust_mass' 680 wtnom(2) = 'dust_number' 681 wtnom(2) = 'dust_number' 681 682 CASE(11) 682 683 wtnom(1) = 'h2o_vap' 683 wtnom(2) = 'h2o_ice' 684 wtnom(2) = 'h2o_ice' 684 685 wtnom(3) = 'dust_mass' 685 686 wtnom(4) = 'dust_number' … … 688 689 CASE(21) 689 690 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' 691 711 END SELECT 692 712 #endif … … 729 749 q_prof(:,1:nq) = SCALAR(i,kps:kpe,j,2:nq+1) !! the names were set above !! one dummy tracer in WRF 730 750 !!! 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 736 755 IF (firstcall .EQV. .true.) THEN 737 756 q_prof(:,:) = 0.95 738 757 ENDIF 739 ENDIF 740 758 ENDIF 741 759 #else 742 760 SELECT CASE (MARS_MODE) … … 841 859 !!!! ADDITIONAL SECURITY. THIS MIGHT HAPPEN WITH OLD INIT FILES. 842 860 IF (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' 844 862 z0_val = 0.01 845 863 ENDIF
Note: See TracChangeset
for help on using the changeset viewer.