program readmeteo implicit none include "netcdf.inc" !------------------------------------------------------------------------! ! Readmeteo prepares an initial state for the WPS pre-processor of WRF ! ! ! ! Input is a diagfi.nc NETCDF file from a LMD/GCM simulation ! ! ! ! Outputs are WRFSI intermediate format files ready for metgrid.exe ! ! http://www.mmm.ucar.edu/wrf/OnLineTutorial/WPS/IM_si.htm ! ! ! ! **** Please create a WPSFEED folder (or a symbolic link) **** ! ! ! ! A. Spiga - 16/04/2007 ! ! 22/05/2007 : need to run zrecast as a preliminary ! ! 07/06/2007 : external parameter file 'readmeteo.def ! ! 30/07/2007 : manage additional variables (tsoil, emiss,...) ! ! 19/10/2007 : no need to run zrecast at all (eta levels) ! ! 12/2007 : include co2ice and emissivity ! ! 02/2008 : include water vapor and ice ! ! 01/2010 : possible use of diagsoil for new physics ! ! 02/2011 : add dust tracers, correct surface ! ! ! ! spiga@lmd.jussieu.fr ! !------------------------------------------------------------------------! !*************************************************************************** !*************************************************************************** REAL, PARAMETER :: emiss_prescribed=0.95 REAL, PARAMETER :: co2ice_prescribed=0. CHARACTER (LEN=3), PARAMETER :: ident='LMD' !*************************************************************************** !*************************************************************************** REAL :: ptop REAL, PARAMETER :: grav=3.72 LOGICAL, PARAMETER :: blank=.false. !! Variables to be written in the output file !! *** NB: conformity with metgrid/src/read_met_module.F90 CHARACTER (LEN=33) :: output INTEGER :: IFV CHARACTER (LEN=24) :: HDATE REAL :: XFCST CHARACTER (LEN=32) :: SOURCE CHARACTER (LEN=9) :: FIELD CHARACTER (LEN=25) :: UNITS CHARACTER (LEN=46) :: DESC REAL :: XLVL INTEGER :: NX,NY,IPROJ CHARACTER (LEN=8) :: STARTLOC REAL :: STARTLAT,STARTLON,DELTALAT,DELTALON REAL, POINTER, DIMENSION(:,:) :: SLAB !! Variables related to NETCDF format integer :: nid,nid2,nid3,nvarid,ierr,ierr2 integer :: timedim,londim,latdim,altdim,altdim2 integer :: rlatvdim,rlonudim integer :: timelen,lonlen,latlen,altlen,altlen2 integer :: rlatvlen,rlonulen integer :: soillen,soildim integer :: nphys integer, dimension(4) :: corner,edges !! Intermediate data arrays integer :: k,l,m,n,p real, dimension(:), allocatable :: lat,lon,time,alt,aps,bps,levels,vertdsoil real, dimension(:,:), allocatable :: vide,ones,ghtsfile real, dimension(:,:), allocatable :: interm real, dimension(:,:,:), allocatable :: gwparam real, dimension(:,:,:), allocatable :: psfile,tsfile real, dimension(:,:,:), allocatable :: emissfile,co2icefile real, dimension(:,:,:), allocatable :: tnsfile,unsfile,vnsfile real, dimension(:,:,:,:), allocatable :: tfile,ufile,vfile,rfile,hfile real, dimension(:,:,:,:), allocatable :: eta_gcm !real, dimension(:,:,:,:), allocatable :: tfileorig,ufileorig,vfileorig real, dimension(:,:,:,:), allocatable :: tsoilfile, dsoilfile, isoilfile real, dimension(:,:,:,:), allocatable :: waterfile, watericefile real, dimension(:,:,:), allocatable :: swatericefile!, swaterfile real, dimension(:,:,:,:), allocatable :: dustfile,dustnfile real, dimension(:,:,:,:), allocatable :: ccnfile,ccnnfile !! Reading the parameter file integer :: tmp,increment,FILES integer :: tmp2,tmp3,tmp4 character*1 :: answer character*4 :: str character*2 :: str2, str3, str4 integer, dimension(:), allocatable :: time_out character*13, dimension(:), allocatable :: date_out character*19, dimension(:), allocatable :: date_out2 #ifdef PHOTOCHEM real, dimension(:,:,:,:,:), allocatable :: chemtrac integer :: nchemtrac,i CHARACTER*20,DIMENSION(:),ALLOCATABLE :: wtnom #endif !*************************************************************************** !*************************************************************************** !!--------------------- !! Open the datafile !!--------------------- ierr=NF_OPEN ("input_diagfi.nc",NF_NOWRITE,nid) IF (ierr.NE.NF_NOERR) THEN write(*,*)'**** Please create a symbolic link called input_diagfi.nc' CALL ABORT ENDIF !!-------------------------- !! Ask for data references !!-------------------------- !write(*,*) "Create n files. What is n ?" read(*,*) FILES allocate(time_out(FILES)) allocate(date_out(FILES)) allocate(date_out2(FILES)) !write(*,*) "" !write(*,*) "INPUT: Diagfi time" !write(*,*) "list of n subscripts, separated by s" increment=1 do while (increment.ne.FILES+1) read(*,*) tmp time_out(increment)=tmp increment=increment+1 enddo !write(*,*) "" !write(*,*) "OUTPUT: WRF time" !write(*,*) "fill 4 lines indicating" !write(*,*) "-year (4 digits)" !write(*,*) "-month (2 digits)" !write(*,*) "-day (2 digits)" !write(*,*) "-hour (2 digits)" increment=1 do while (increment.ne.FILES+1) read(*,*) str read(*,*) str2 read(*,*) str3 read(*,*) str4 date_out(increment)=str//'-'//str2//'-'//str3//'_'//str4 date_out2(increment)=str//'-'//str2//'-'//str3//'_'//str4//':00:00' !print *,date_out(increment) !write(*,*) "ok? (y/n)" read(*,*) answer if (answer.eq.'n') then !write(*,*) "please write again" else !write(*,*) "next one, please" increment=increment+1 endif enddo !!------------------- !! Get array sizes !!------------------- SELECT CASE(ident) CASE('LMD') ierr=NF_INQ_DIMID(nid,"Time",timedim) CASE('OXF') ierr=NF_INQ_DIMID(nid,"time",timedim) END SELECT ierr=NF_INQ_DIMLEN(nid,timedim,timelen) write(*,*) "timelen: ",timelen SELECT CASE(ident) CASE('LMD') ierr=NF_INQ_DIMID(nid,"latitude",latdim) CASE('OXF') ierr=NF_INQ_DIMID(nid,"lat",latdim) END SELECT ierr=NF_INQ_DIMLEN(nid,latdim,latlen) write(*,*) "latlen: ",latlen SELECT CASE(ident) CASE('LMD') ierr=NF_INQ_DIMID(nid,"longitude",londim) CASE('OXF') ierr=NF_INQ_DIMID(nid,"lon",londim) END SELECT ierr=NF_INQ_DIMLEN(nid,londim,lonlen) write(*,*) "lonlen: ",lonlen SELECT CASE(ident) CASE('LMD') ierr=NF_INQ_DIMID(nid,"altitude",altdim) CASE('OXF') ierr=NF_INQ_DIMID(nid,"sigma",altdim) END SELECT ierr=NF_INQ_DIMLEN(nid,altdim,altlen) write(*,*) "altlen: ",altlen !!------------------------- !! Allocate local arrays !!------------------------- allocate(eta_gcm(lonlen,latlen,altlen,timelen)) allocate(tfile(lonlen,latlen,altlen,timelen)) allocate(tsoilfile(lonlen,latlen,altlen,timelen)) allocate(dsoilfile(lonlen,latlen,altlen,timelen)) allocate(isoilfile(lonlen,latlen,altlen,timelen)) allocate(vertdsoil(altlen)) !allocate(tfileorig(lonlen,latlen,altlen,timelen)) allocate(ufile(lonlen,latlen,altlen,timelen)) !allocate(ufileorig(lonlen,latlen,altlen,timelen)) allocate(vfile(lonlen,latlen,altlen,timelen)) !allocate(vfileorig(lonlen,latlen,altlen,timelen)) allocate(rfile(lonlen,latlen,altlen,timelen)) allocate(hfile(lonlen,latlen,altlen,timelen)) allocate(waterfile(lonlen,latlen,altlen,timelen)) allocate(watericefile(lonlen,latlen,altlen,timelen)) !allocate(swaterfile(lonlen,latlen,timelen)) allocate(swatericefile(lonlen,latlen,timelen)) allocate(dustfile(lonlen,latlen,altlen,timelen)) allocate(dustnfile(lonlen,latlen,altlen,timelen)) allocate(ccnfile(lonlen,latlen,altlen,timelen)) allocate(ccnnfile(lonlen,latlen,altlen,timelen)) allocate(psfile(lonlen,latlen,timelen)) allocate(tsfile(lonlen,latlen,timelen)) allocate(tnsfile(lonlen,latlen,timelen)) allocate(unsfile(lonlen,latlen,timelen)) allocate(vnsfile(lonlen,latlen,timelen)) allocate(emissfile(lonlen,latlen,timelen)) allocate(co2icefile(lonlen,latlen,timelen)) allocate(interm(lonlen,latlen)) allocate(gwparam(lonlen,latlen,5)) allocate(ghtsfile(lonlen,latlen)) !! no scan axis allocate(vide(lonlen,latlen)) allocate(ones(lonlen,latlen)) allocate(lat(latlen), lon(lonlen), alt(altlen), time(timelen)) allocate(aps(altlen),bps(altlen),levels(altlen)) #ifdef PHOTOCHEM nchemtrac = 14 allocate(wtnom(nchemtrac)) wtnom(1) = "c_co2" wtnom(2) = "c_co" wtnom(3) = "c_o" wtnom(4) = "c_o1d" wtnom(5) = "c_o2" wtnom(6) = "c_o3" wtnom(7) = "c_h" wtnom(8) = "c_h2" wtnom(9) = "c_oh" wtnom(10) = "c_ho2" wtnom(11) = "c_h2o2" wtnom(12) = "c_ch4" wtnom(13) = "c_n2" wtnom(14) = "c_ar" allocate(chemtrac(lonlen,latlen,altlen,timelen,nchemtrac)) chemtrac(:,:,:,:,:)=0 #endif tfile(:,:,:,:)=0 tsoilfile(:,:,:,:)=0 isoilfile(:,:,:,:)=0 dsoilfile(:,:,:,:)=0 vertdsoil(:)=0. !tfileorig(:,:,:,:)=0 !ufileorig(:,:,:,:)=0 !vfileorig(:,:,:,:)=0 ufile(:,:,:,:)=0 vfile(:,:,:,:)=0 rfile(:,:,:,:)=0 hfile(:,:,:,:)=0 waterfile(:,:,:,:)=0 watericefile(:,:,:,:)=0 !swaterfile(:,:,:)=0 swatericefile(:,:,:)=0 dustfile(:,:,:,:)=0 dustnfile(:,:,:,:)=0 ccnfile(:,:,:,:)=0 ccnnfile(:,:,:,:)=0 psfile(:,:,:)=0 tsfile(:,:,:)=0 emissfile(:,:,:)=0 co2icefile(:,:,:)=0 tnsfile(:,:,:)=0 unsfile(:,:,:)=0 vnsfile(:,:,:)=0 interm(:,:)=0 gwparam(:,:,:)=0 ghtsfile(:,:)=0 vide(:,:)=0 ones(:,:)=0 !!------------------- !! Read dimensions !!------------------- print *,'>>> Read dimensions !' print *,'Time' SELECT CASE(ident) CASE('LMD') ierr = NF_INQ_VARID (nid, "Time",nvarid) CASE('OXF') ierr = NF_INQ_VARID (nid, "time",nvarid) END SELECT IF (ierr .NE. NF_NOERR) THEN PRINT *, "Error: Readmeteo