Ignore:
Timestamp:
Sep 6, 2011, 11:02:38 AM (13 years ago)
Author:
emillour
Message:

Update utilitaire "concatnc" du GCM Mars.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/util/concatnc.F90

    r137 r280  
    1010!   to output file (E. Millour, september 2006)
    1111!   if available (F. Forget, october 2006)
     12! + handle 1D data (EM, January 2007)
    1213! + ap(), bp()  (F. Forget, February 2008)
     14! + handle the possibility that number of GCM layers (aps, bps
     15!   or sigma) may be different from number of vertical levels
     16!   of data (which is the case for outputs from 'zrecast')
     17!   (EM, April 2010)
    1318! ********************************************************
    1419
     
    1722include "netcdf.inc" ! NetCDF definitions
    1823
    19 character (len=50), dimension(200) :: file
     24character (len=50), dimension(1000) :: file
    2025! file(): input file(s) names(s)
    2126character (len=30), dimension(15) :: notconcat
     
    4348integer :: varid
    4449! varid: [netcdf] variable ID #
    45 integer :: memolatlen,memolonlen,memoaltlen
     50integer :: memolatlen=0,memolonlen=0,memoaltlen=0
    4651! memolatlen: # of elements of lat(), read from the first input file
    4752! memolonlen: # of elements of lon(), read from the first input file
     
    6267! altdim: [netcdf] "altdim" dim ID
    6368! timedim: [netcdf] "timedim" dim ID
     69integer :: gcmlayerdim ! NetCDF dimension ID for # of layers in GCM
    6470integer :: latvar,lonvar,altvar,timevar
    6571! latvar: [netcdf] ID of "latitude" variable
     
    7278! altvar: # of elements of alt() array
    7379! timelen: # of elemnets of time() array
    74 integer :: nout,latdimout,londimout,altdimout,apdimout,timedimout,timevarout
     80integer :: GCM_layers ! number of GCM atmospheric layers (may not be
     81! same as altlen if file is an output of zrecast)
     82integer :: nout,latdimout,londimout,altdimout,timedimout,timevarout
    7583! nout: [netcdf] output file ID
    7684! latdimout: [netcdf] output latitude (dimension) ID
     
    7987! timedimout: [netcdf] output time (dimension) ID
    8088! timevarout: [netcdf] ID of output "Time" variable
     89integer :: layerdimout ! NetCDF dimension ID for # of layers in GCM
     90integer :: interlayerdimout ! dimension ID for # of interlayers in GCM
    8191integer :: reptime,rep,varidout
    8292! reptime: total length of concatenated time() arrays
     
    308318!  write(*,*) "altlen: ",altlen
    309319
     320! load size of aps() or sigma() (in case it is not altlen)
     321   ! default is that GCM_layers=altlen
     322   ! but for outputs of zrecast, it may be a different value
     323   ierr=NF_INQ_DIMID(nid,"GCM_layers",gcmlayerdim)
     324   if (ierr.ne.NF_NOERR) then
     325     ! didn't find a GCM_layers dimension; therefore we have:
     326     GCM_layers=altlen
     327   else
     328     ! load value of GCM_layers
     329     ierr=NF_INQ_DIMLEN(nid,gcmlayerdim,GCM_layers)
     330   endif
     331!   write(*,*) "GCM_layers=",GCM_layers
     332
    310333!==============================================================================
    311334! 2.3. Read (and check compatibility of) dimensions of
     
    330353#endif
    331354   ! Initialize output file's lat,lon,alt and time dimensions
    332       call initiate (filename,lat,lon,alt,nout,&
    333            latdimout,londimout,altdimout,apdimout,timedimout,timevarout)
     355      call initiate (filename,lat,lon,alt,GCM_layers,nout,&
     356       latdimout,londimout,altdimout,timedimout,&
     357       layerdimout,interlayerdimout,timevarout)
    334358   ! Initialize output file's aps,bps,ap,bp and phisinit variables
    335      call init2(nid,lonlen,latlen,altlen,&
    336                 nout,londimout,latdimout,altdimout,apdimout)
     359     call init2(nid,lonlen,latlen,altlen,GCM_layers,&
     360                nout,londimout,latdimout,altdimout,&
     361                layerdimout,interlayerdimout)
    337362   
    338363   else ! Not a first call,
     
    424449      ! build dim(),corner() and edges() arrays
    425450      ! and allocate var3d() array
    426       if (ndim==3) then
     451      if (ndim==1) then
     452         allocate(var3d(timelen,1,1,1))
     453         dim(1)=timedimout
     454
     455         ! start indexes (where data values will be written)
     456         corner(1)=reptime+1
     457         corner(2)=1
     458         corner(3)=1
     459         corner(4)=1
     460
     461         ! length (along dimensions) of block of data to be written
     462         edges(1)=timelen
     463         edges(2)=1
     464         edges(3)=1
     465         edges(4)=1
     466
     467      else if (ndim==3) then
    427468         allocate(var3d(lonlen,latlen,timelen,1))
    428469         dim(1)=londimout
     
    527568
    528569!******************************************************************************
    529 Subroutine initiate (filename,lat,lon,alt,&
    530          nout,latdimout,londimout,altdimout,apdimout,timedimout,timevarout)
     570subroutine initiate (filename,lat,lon,alt,GCM_layers,nout,&
     571         latdimout,londimout,altdimout,timedimout,&
     572         layerdimout,interlayerdimout,timevarout)
    531573!==============================================================================
    532574! Purpose:
     
    552594real, dimension(:), intent(in):: alt
    553595! alt(): altitude
     596integer,intent(in) :: GCM_layers ! number of GCM layers
    554597integer, intent(out):: nout
    555598! nout: [netcdf] file ID
     
    560603integer, intent(out):: altdimout
    561604! altdimout: [netcdf] alt()  ID
    562 integer, intent(out):: apdimout
    563 ! apdimout: [netcdf] ap()  ID
    564605integer, intent(out):: timedimout
    565606! timedimout: [netcdf] "Time"  ID
     607integer,intent(out) :: layerdimout
     608! layerdimout: [netcdf] "GCM_layers" ID
     609integer,intent(out) :: interlayerdimout
     610! layerdimout: [netcdf] "GCM_layers+1" ID
    566611integer, intent(out):: timevarout
    567612! timevarout: [netcdf] "Time" (considered as a variable) ID
     
    593638ierr = NF_DEF_DIM(nout, "longitude", size(lon), londimout)
    594639ierr = NF_DEF_DIM(nout, "altitude", size(alt), altdimout)
    595 ierr = NF_DEF_DIM(nout, "interlayer",(size(alt)+1), apdimout)
    596640ierr = NF_DEF_DIM(nout, "Time", NF_UNLIMITED, timedimout)
     641ierr = NF_DEF_DIM(nout, "GCM_layers", GCM_layers, layerdimout)
     642ierr = NF_DEF_DIM(nout, "GCM_interlayers",GCM_layers+1,interlayerdimout)
    597643
    598644! End netcdf define mode
     
    660706end Subroutine initiate
    661707!******************************************************************************
    662 subroutine init2(infid,lonlen,latlen,altlen, &
    663                  outfid,londimout,latdimout,altdimout,apdimout)
     708subroutine init2(infid,lonlen,latlen,altlen,GCM_layers, &
     709                 outfid,londimout,latdimout,altdimout, &
     710                 layerdimout,interlayerdimout)
    664711!==============================================================================
    665712! Purpose:
    666 ! Copy aps(), bps() and phisinit() from input file to outpout file
    667 ! Copy ap(), bp() from input file to outpout file
     713! Copy ap() , bp(), aps(), bps() and phisinit() from input file to outpout file
    668714!==============================================================================
    669715! Remarks:
     
    682728integer, intent(in) :: latlen ! # of grid points along latitude
    683729integer, intent(in) :: altlen ! # of grid points along latitude
     730integer, intent(in) :: GCM_layers ! # of GCM atmospheric layers
    684731integer, intent(in) :: outfid ! NetCDF output file ID
    685732integer, intent(in) :: londimout ! longitude dimension ID
    686733integer, intent(in) :: latdimout ! latitude dimension ID
    687734integer, intent(in) :: altdimout ! altitude dimension ID
    688 integer, intent(in) :: apdimout ! interlayer dimension ID
     735integer, intent(in) :: layerdimout ! GCM_layers dimension ID
     736integer, intent(in) :: interlayerdimout ! GCM_layers+1 dimension ID
    689737!==============================================================================
    690738! Local variables:
     
    692740real,dimension(:),allocatable :: aps,bps ! hybrid vertical coordinates
    693741real,dimension(:),allocatable :: ap,bp ! hybrid vertical coordinates
     742real,dimension(:),allocatable :: sigma ! sigma levels
    694743real,dimension(:,:),allocatable :: phisinit ! Ground geopotential
    695 integer :: apsid,bpsid,phisinitid
     744integer :: apsid,bpsid,sigmaid,phisinitid
    696745integer :: apid,bpid
    697746integer :: ierr
    698747integer :: tmpvarid ! temporary variable ID
    699748logical :: phis ! is "phisinit" available ?
    700 logical :: hybrid ! are "aps" "bps" "ap" "bp" available ?
     749logical :: hybrid ! are "aps" and "bps" available ?
    701750
    702751!==============================================================================
     
    705754
    706755! hybrid coordinate aps
    707 allocate(aps(altlen))
     756!write(*,*) "aps: altlen=",altlen," GCM_layers=",GCM_layers
     757allocate(aps(GCM_layers),stat=ierr)
     758if (ierr.ne.0) then
     759  write(*,*) "init2: failed to allocate aps!"
     760  stop
     761endif
    708762ierr=NF_INQ_VARID(infid,"aps",tmpvarid)
    709763if (ierr.ne.NF_NOERR) then
    710   write(*,*) "Ooops. Failed to get aps ID. OK."
     764  write(*,*) "Ooops. Failed to get aps ID. OK, will look for sigma coord."
    711765  hybrid=.false.
    712766else
     
    714768  hybrid=.true.
    715769  if (ierr.ne.NF_NOERR) then
    716     stop "Error: Failed reading aps"
    717   endif
    718 endif
    719 
    720 ! hybrid coordinate bps
    721 allocate(bps(altlen))
    722 ierr=NF_INQ_VARID(infid,"bps",tmpvarid)
     770    stop "init2 Error: Failed reading aps"
     771  endif
     772
     773  ! hybrid coordinate bps
     774!  write(*,*) "bps: altlen=",altlen," GCM_layers=",GCM_layers
     775  allocate(bps(GCM_layers),stat=ierr)
     776  if (ierr.ne.0) then
     777    write(*,*) "init2: failed to allocate bps!"
     778    stop
     779  endif
     780  ierr=NF_INQ_VARID(infid,"bps",tmpvarid)
     781  if (ierr.ne.NF_NOERR) then
     782    stop "init2 Error: Failed to get bps ID."
     783  endif
     784  ierr=NF_GET_VAR_REAL(infid,tmpvarid,bps)
     785  if (ierr.ne.NF_NOERR) then
     786    stop "init2 Error: Failed reading bps"
     787  endif
     788endif
     789
     790! hybrid coordinate ap
     791allocate(ap(GCM_layers+1),stat=ierr)
     792if (ierr.ne.0) then
     793  write(*,*) "init2: failed to allocate ap!"
     794  stop
     795else
     796  ierr=NF_INQ_VARID(infid,"ap",tmpvarid)
     797  if (ierr.ne.NF_NOERR) then
     798    write(*,*) "Ooops. Failed to get ap ID. OK."
     799    hybrid=.false.
     800  else
     801    ierr=NF_GET_VAR_REAL(infid,tmpvarid,ap)
     802    hybrid=.true.
     803    if (ierr.ne.NF_NOERR) then
     804      stop "Error: Failed reading ap"
     805    endif
     806  endif
     807endif
     808
     809! hybrid coordinate bp
     810allocate(bp(GCM_layers+1),stat=ierr)
     811if (ierr.ne.0) then
     812  write(*,*) "init2: failed to allocate bp!"
     813  stop
     814else
     815  ierr=NF_INQ_VARID(infid,"bp",tmpvarid)
     816  if (ierr.ne.NF_NOERR) then
     817    write(*,*) "Ooops. Failed to get bp ID. OK."
     818    hybrid=.false.
     819  else
     820    ierr=NF_GET_VAR_REAL(infid,tmpvarid,bp)
     821    hybrid=.true.
     822    if (ierr.ne.NF_NOERR) then
     823      stop "Error: Failed reading bp"
     824    endif
     825  endif
     826endif
     827
     828! sigma levels (if any)
     829if (.not.hybrid) then
     830  allocate(sigma(GCM_layers),stat=ierr)
     831  if (ierr.ne.0) then
     832    write(*,*) "init2: failed to allocate sigma"
     833    stop
     834  endif
     835  ierr=NF_INQ_VARID(infid,"sigma",tmpvarid)
     836  ierr=NF_GET_VAR_REAL(infid,tmpvarid,sigma)
     837  if (ierr.ne.NF_NOERR) then
     838    stop "init2 Error: Failed reading sigma"
     839  endif
     840endif ! of if (.not.hybrid)
     841
     842! ground geopotential phisinit
     843allocate(phisinit(lonlen,latlen),stat=ierr)
     844if (ierr.ne.0) then
     845  write(*,*) "init2: failed to allocate phisinit!"
     846  stop
     847endif
     848ierr=NF_INQ_VARID(infid,"phisinit",tmpvarid)
    723849if (ierr.ne.NF_NOERR) then
    724   write(*,*) "Ooops. Failed to get bps ID. OK."
    725   hybrid=.false.
    726 else
    727   ierr=NF_GET_VAR_REAL(infid,tmpvarid,bps)
    728   hybrid=.true.
    729   if (ierr.ne.NF_NOERR) then
    730     stop "Error: Failed reading bps"
    731   endif
    732 endif
    733 
    734 ! hybrid coordinate ap
    735 allocate(ap(altlen+1))
    736 ierr=NF_INQ_VARID(infid,"ap",tmpvarid)
    737 if (ierr.ne.NF_NOERR) then
    738   write(*,*) "Ooops. Failed to get ap ID. OK."
    739   hybrid=.false.
    740 else
    741   ierr=NF_GET_VAR_REAL(infid,tmpvarid,ap)
    742   hybrid=.true.
    743   if (ierr.ne.NF_NOERR) then
    744     stop "Error: Failed reading ap"
    745   endif
    746 endif
    747 
    748 ! hybrid coordinate bp
    749 allocate(bp(altlen+1))
    750 ierr=NF_INQ_VARID(infid,"bp",tmpvarid)
    751 if (ierr.ne.NF_NOERR) then
    752   write(*,*) "Ooops. Failed to get bp ID. OK."
    753   hybrid=.false.
    754 else
    755   ierr=NF_GET_VAR_REAL(infid,tmpvarid,bp)
    756   hybrid=.true.
    757   if (ierr.ne.NF_NOERR) then
    758     stop "Error: Failed reading bp"
    759   endif
    760 endif
    761 
    762 ! ground geopotential phisinit
    763 ! ground geopotential phisinit
    764 ierr=NF_INQ_VARID(infid,"phisinit",tmpvarid)
    765 allocate(phisinit(lonlen,latlen))
    766 if (ierr.ne.NF_NOERR) then
    767   write(*,*) "Failed to get phisinit ID. We must be reading a ""stats"" file"
    768   phisinit = 0.
     850  write(*,*)"init2 warning: Failed to get phisinit ID."
    769851  phis = .false.
    770852else
    771853  ierr=NF_GET_VAR_REAL(infid,tmpvarid,phisinit)
    772854  if (ierr.ne.NF_NOERR) then
    773     stop "Error: Failed reading phisinit"
     855    stop "init2 Error: Failed reading phisinit"
    774856  endif
    775857  phis = .true.
     
    781863
    782864!==============================================================================
    783 ! 2.2. Hybrid coordinates aps() and bps()
     865! 2.2. Hybrid coordinates ap() , bp(), aps() and bps()
    784866!==============================================================================
    785867if(hybrid) then
    786868! define aps
    787869  call def_var(nout,"aps","hybrid pressure at midlayers"," ",1,&
    788              (/altdimout/),apsid,ierr)
    789   if (ierr.ne.NF_NOERR) then
    790     stop "Error: Failed to def_var aps"
     870             (/layerdimout/),apsid,ierr)
     871  if (ierr.ne.NF_NOERR) then
     872    stop "init2 Error: Failed to def_var aps"
    791873  endif
    792874
     
    798880#endif
    799881  if (ierr.ne.NF_NOERR) then
    800     stop "Error: Failed to write aps"
     882    stop "init2 Error: Failed to write aps"
    801883  endif
    802884
    803885! define bps
    804886  call def_var(nout,"bps","hybrid sigma at midlayers"," ",1,&
    805              (/altdimout/),bpsid,ierr)
    806   if (ierr.ne.NF_NOERR) then
    807     stop "Error: Failed to def_var bps"
     887             (/layerdimout/),bpsid,ierr)
     888  if (ierr.ne.NF_NOERR) then
     889    stop "init2 Error: Failed to def_var bps"
    808890  endif
    809891
     
    815897#endif
    816898  if (ierr.ne.NF_NOERR) then
    817     stop "Error: Failed to write bps"
     899    stop "init2 Error: Failed to write bps"
    818900  endif
    819901
    820902! define ap
    821903  call def_var(nout,"ap","hybrid sigma at interlayers"," ",1,&
    822              (/apdimout/),apid,ierr)
     904             (/interlayerdimout/),apid,ierr)
    823905  if (ierr.ne.NF_NOERR) then
    824906    stop "Error: Failed to def_var ap"
     
    837919! define bp
    838920  call def_var(nout,"bp","hybrid sigma at interlayers"," ",1,&
    839              (/apdimout/),bpid,ierr)
     921             (/interlayerdimout/),bpid,ierr)
    840922  if (ierr.ne.NF_NOERR) then
    841923    stop "Error: Failed to def_var bp"
     
    851933    stop "Error: Failed to write bp"
    852934  endif
    853 endif
     935
     936else
     937! define sigma
     938  call def_var(nout,"sigma","sigma at midlayers"," ",1,&
     939             (/layerdimout/),sigmaid,ierr)
     940  if (ierr.ne.NF_NOERR) then
     941    stop "init2 Error: Failed to def_var sigma"
     942  endif
     943! write sigma
     944#ifdef NC_DOUBLE
     945  ierr=NF_PUT_VAR_DOUBLE(outfid,sigmaid,sigma)
     946#else
     947  ierr=NF_PUT_VAR_REAL(outfid,sigmaid,sigma)
     948#endif
     949  if (ierr.ne.NF_NOERR) then
     950    stop "init2 Error: Failed to write sigma"
     951  endif
     952endif ! of if (hybrid)
    854953
    855954!==============================================================================
     
    859958IF (phis) THEN
    860959
    861 !define phisinit
    862  call def_var(nout,"phisinit","Ground level geopotential"," ",2,&
     960  !define phisinit
     961   call def_var(nout,"phisinit","Ground level geopotential"," ",2,&
    863962            (/londimout,latdimout/),phisinitid,ierr)
    864  if (ierr.ne.NF_NOERR) then
    865      stop "Error: Failed to def_var phisinit"
    866   endif
    867 
    868 ! write phisinit
    869 #ifdef NC_DOUBLE
    870 ierr=NF_PUT_VAR_DOUBLE(outfid,phisinitid,phisinit)
    871 #else
    872 ierr=NF_PUT_VAR_REAL(outfid,phisinitid,phisinit)
    873 #endif
    874 if (ierr.ne.NF_NOERR) then
    875   stop "Error: Failed to write phisinit"
    876 endif
    877 
    878 ENDIF
     963   if (ierr.ne.NF_NOERR) then
     964     stop "init2 Error: Failed to def_var phisinit"
     965   endif
     966
     967  ! write phisinit
     968#ifdef NC_DOUBLE
     969  ierr=NF_PUT_VAR_DOUBLE(outfid,phisinitid,phisinit)
     970#else
     971  ierr=NF_PUT_VAR_REAL(outfid,phisinitid,phisinit)
     972#endif
     973  if (ierr.ne.NF_NOERR) then
     974    stop "init2 Error: Failed to write phisinit"
     975  endif
     976
     977ENDIF ! of IF (phis)
    879978
    880979
    881980! Cleanup
    882 deallocate(aps)
    883 deallocate(bps)
    884 deallocate(ap)
    885 deallocate(bp)
    886 deallocate(phisinit)
     981if (allocated(aps)) deallocate(aps)
     982if (allocated(bps)) deallocate(bps)
     983if (allocated(ap)) deallocate(ap)
     984if (allocated(bp)) deallocate(bp)
     985if (allocated(sigma)) deallocate(sigma)
     986if (allocated(phisinit)) deallocate(phisinit)
    887987
    888988end subroutine init2
Note: See TracChangeset for help on using the changeset viewer.