Changeset 2269 in lmdz_wrf for trunk/tools
- Timestamp:
- Dec 27, 2018, 3:14:51 PM (6 years ago)
- Location:
- trunk/tools
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/tools/module_scientific.f90
r2268 r2269 57 57 ! sort_polygon: Subroutine to sort a polygon using its center as average of the coordinates and remove duplicates 58 58 ! SortR_K*: Subroutine receives an array x() r_K and sorts it into ascending order. 59 ! spacepercen: Subroutine to compute the space-percentages of a series of grid cells (B) into another series of grid-cells (A) 60 ! spaceweightstats: Subroutine to compute an spatial statistics value from a matrix B into a matrix A using weights 59 61 ! StatsR_K: Subroutine to provide the minmum, maximum, mean, the quadratic mean, and the standard deviation of a 60 62 ! series of r_k numbers … … 4932 4934 END SUBROUTINE spacepercen_within_reg 4933 4935 4934 SUBROUTINE spacepercen( dxA, dyA, xCAvals, yCAvals, NAvertexmax, xBAvals, yBAvals, dxB, dyB, xCBvals,&4935 yCBvals, NBvertexmax, xBBvals, yBBvals, dxyB, strict, Ngridsin, gridsin, percentages)4936 SUBROUTINE spacepercen(xCAvals, yCAvals, xBAvals, yBAvals, xCBvals, yCBvals, xBBvals, yBBvals, & 4937 dxA, dyA, NAvertexmax, dxB, dyB, dxyB, NBvertexmax, strict, Ngridsin, gridsin, percentages) 4936 4938 ! Subroutine to compute the space-percentages of a series of grid cells (B) into another series of 4937 4939 ! grid-cells (A) … … 4941 4943 IMPLICIT NONE 4942 4944 4943 INTEGER, INTENT(in) :: dxA, dyA, NAvertexmax , dxB, dyB, &4944 4945 INTEGER, INTENT(in) :: dxA, dyA, NAvertexmax 4946 INTEGER, INTENT(in) :: dxB, dyB, NBvertexmax, dxyB 4945 4947 REAL(r_k), DIMENSION(dxA,dyA), INTENT(in) :: xCAvals, yCAvals 4946 4948 REAL(r_k), DIMENSION(dxB,dyB), INTENT(in) :: xCBvals, yCBvals … … 4954 4956 ! Local 4955 4957 INTEGER :: iv, ix, iy 4956 INTEGER :: Nvertex , NvertexAgrid, Ncoin, Nsort4958 INTEGER :: Nvertex 4957 4959 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: poinsin 4958 4960 CHARACTER(len=20) :: DS 4959 REAL(r_k) :: areapoly, areagpoly, totarea, totpercent4960 4961 REAL(r_k), ALLOCATABLE, DIMENSION(:,:) :: vertexgrid 4961 4962 … … 4982 4983 Nvertex = 0 4983 4984 DO iv=1, NAvertexmax 4984 IF (xBAvals(ix,iy,iv) /= fillval I) THEN4985 IF (xBAvals(ix,iy,iv) /= fillval64) THEN 4985 4986 Nvertex = Nvertex + 1 4986 4987 END IF … … 4993 4994 CALL grid_within_polygon(Nvertex, vertexgrid, dxB, dyB, dxB*dyB, xCBvals, yCBvals, NBvertexmax, & 4994 4995 xBBvals, yBBvals, Ngridsin(ix,iy), gridsin(ix,iy,:,:)) 4996 4995 4997 IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin) 4996 4998 ALLOCATE(poinsin(Ngridsin(ix,iy),2)) … … 5004 5006 Ngridsin(ix,iy), poinsin, strict, percentages(ix,iy,:)) 5005 5007 5006 END DO5007 5008 END DO 5009 END DO 5008 5010 5009 5011 END SUBROUTINE spacepercen 5010 5012 5013 SUBROUTINE spaceweightstats(varin, Ngridsin, gridsin, percentages, stats, varout, dxA, dyA, dxB, & 5014 dyB, maxNgridsin, Lstats) 5015 ! Subroutine to compute an spatial statistics value from a matrix B into a matrix A using weights 5016 5017 IMPLICIT NONE 5018 5019 INTEGER, INTENT(in) :: dxA, dyA, dxB, dyB, maxNgridsin, Lstats 5020 CHARACTER(len=60), INTENT(in) :: stats 5021 INTEGER, DIMENSION(dxA,dyA), INTENT(in) :: Ngridsin 5022 INTEGER, DIMENSION(dxA,dyA,maxNgridsin,2), INTENT(in):: gridsin 5023 REAL(r_k), DIMENSION(dxB,dyB), INTENT(out) :: varin 5024 REAL(r_k), DIMENSION(dxA,dyA,maxNgridsin), INTENT(in):: percentages 5025 REAL(r_k), DIMENSION(dxA,dyA,Lstats), INTENT(out) :: varout 5026 5027 ! Local 5028 INTEGER :: ix, iy, iv, ii, jj 5029 5030 !!!!!!! Variables 5031 ! dxA, dyA: length of dimensions of matrix A 5032 ! dxB, dyB: length of dimensions of matrix B 5033 ! maxNgridsin: maximum number of grid points from B to be used to compute into a grid of matrix A 5034 ! Lstats: length of the dimension of the statistics 5035 ! varin: variable from matrix B to be used 5036 ! Ngridsin: number of grids from matrix B for each grid of matrix A 5037 ! gridsin: coordinates of grids of matrix B for each grid of matrix A 5038 ! percentages: weights as percentages of space of grid in matrix A covered by grid of matrix B 5039 ! stats: name of the spatial statistics to compute inside each grid of matrix A using values from 5040 ! matrix B. Avaialbe ones: 5041 ! 'min': minimum value 5042 ! 'max': maximum value 5043 ! 'mean': mean value 5044 ! 'mean2': quadratic mean value 5045 ! 'stddev': standard deviation value 5046 ! 'count': percentage of the space of matrix A covered by each different value of matrix B 5047 ! varout: output statistical variable 5048 5049 fname = 'spaceweightstats' 5050 5051 ! Let's be efficvient? 5052 statn: SELECT CASE(TRIM(stats)) 5053 CASE('min') 5054 varout = fillVal64 5055 DO ix=1, dxA 5056 DO iy=1, dyA 5057 DO iv=1, Ngridsin(ix,iy) 5058 ii = gridsin(ix,iy,iv,1) 5059 jj = gridsin(ix,iy,iv,2) 5060 IF (varin(ii,jj) < varout(ix,iy,Lstats)) varout(ix,iy,1) = varin(ii,jj) 5061 END DO 5062 END DO 5063 END DO 5064 CASE DEFAULT 5065 msg = "statisitcs '" // TRIM(stats) // "' not ready !!" // CHAR(44) // " available ones: " // & 5066 "'min', 'max', 'mean', 'mean2', 'stddev', 'count'" 5067 CALL ErrMsg(msg, fname, -1) 5068 END SELECT statn 5069 5070 END SUBROUTINE spaceweightstats 5071 5011 5072 END MODULE module_scientific -
trunk/tools/nc_var_tools.py
r2268 r2269 27351 27351 refdx = reflon.shape[1] 27352 27352 refdy = reflon.shape[0] 27353 refmaxvert = refvarbndsx.shape[ 2]27353 refmaxvert = refvarbndsx.shape[0] 27354 27354 27355 27355 else: … … 27441 27441 ovarxbnds = oncget.variables[getvarxbndsn] 27442 27442 ovary = oncget.variables[getvaryn] 27443 ovarybnds = oncget.variables[getvarybndsn] 27443 27444 27444 27445 sgetvarx, dims = SliceVarDict(ovarx,slicedict) … … 27452 27453 getdx = getlon.shape[1] 27453 27454 getdy = getlon.shape[0] 27454 getmaxvert = getvarbndsx.shape[ 2]27455 getmaxvert = getvarbndsx.shape[0] 27455 27456 27456 27457 iif = iif + 1 … … 27465 27466 getvarybndst = getvarbndsy.transpose() 27466 27467 27467 Ngridsint, gridsint, percenst = fsci.module_scientific.spacepercen(dxa=refdx, \ 27468 dya=refdy, xcavals=reflont, ycavals=reflatt, navertexmax=refmaxvert, \ 27469 xbavals=refvarxbndst, ybavals=refvarybndst, \ 27470 dxb=getdx, dyb=getdy, dxyb=getdx*getdy, xcbvals=getlont, ycbvals=getlatt, \ 27471 nbvertexmax=getmaxvert, xbbvals=getvarxbndst, ybbvals=getvarybndst, \ 27472 strict=strict) 27473 27474 Ngridsin = Ngridint.transpose() 27475 gridsin = gridint.transpose() 27468 Ngridsint, gridsint, percenst = fsci.module_scientific.spacepercen( \ 27469 xcavals=reflont, ycavals=reflatt, xbavals=refvarxbndst, ybavals=refvarybndst, \ 27470 xcbvals=getlont, ycbvals=getlatt, xbbvals=getvarxbndst, ybbvals=getvarybndst, \ 27471 strict=strict, dxa=refdx, dya=refdy, navertexmax=refmaxvert, \ 27472 dxb=getdx, dyb=getdy, dxyb=getdx*getdy, nbvertexmax=getmaxvert) 27473 27474 Ngridsin = Ngridsint.transpose() 27475 gridsin = gridsint.transpose() 27476 27476 percens = percenst.transpose() 27477 27477 … … 27484 27484 newdim = onewnc.createDimension('lat',refdy) 27485 27485 newdim = onewnc.createDimension('bnds',refmaxvert) 27486 newdim = onewnc.createDimension('gridin',np.max( gridsin))27487 newdim = onewnc.createDimension('coord s',2)27486 newdim = onewnc.createDimension('gridin',np.max(Ngridsin)) 27487 newdim = onewnc.createDimension('coord',2) 27488 27488 27489 27489 # variable-dimensions 27490 27490 newvar = onewnc.createVariable('lon','f8',('lat','lon')) 27491 newvar[:] = reflon 27491 newvar[:] = reflon[:] 27492 27492 basicvardef(newvar,'longitude','Longitude','degrees_east') 27493 new avr.setncattr('bounds','lon_bnds')27493 newvar.setncattr('bounds','lon_bnds') 27494 27494 27495 27495 newvar = onewnc.createVariable('lon_bnds','f8',('bnds', 'lat','lon')) 27496 newvar[:] = refvar xbnds27496 newvar[:] = refvarbndsx[:] 27497 27497 basicvardef(newvar,'longitude_bnds','Bounds of Longitude','degrees_east') 27498 27498 27499 27499 newvar = onewnc.createVariable('lat','f8',('lat','lon')) 27500 newvar[:] = reflat 27500 newvar[:] = reflat[:] 27501 27501 basicvardef(newvar,'latitude','Latitude','degrees_north') 27502 new avr.setncattr('bounds','lat_bnds')27502 newvar.setncattr('bounds','lat_bnds') 27503 27503 27504 27504 newvar = onewnc.createVariable('lat_bnds','f8',('bnds', 'lat','lon')) 27505 newvar[:] = refvar ybnds27505 newvar[:] = refvarbndsy[:] 27506 27506 basicvardef(newvar,'latitude_bnds','Bounds of Latitude','degrees_north') 27507 27507 27508 27508 # variables space-weight 27509 newvar = onewnc.createVariable('Ngrid','i',(' gridin', 'lat','lon'))27510 newvar[:] = Ngridsin 27509 newvar = onewnc.createVariable('Ngrid','i',('lat','lon')) 27510 newvar[:] = Ngridsin[:] 27511 27511 basicvardef(newvar, 'Ngrid', "number of grids cells grom 'get' laying within" + \ 27512 27512 " 'ref'",'-') 27513 newavr.setncattr('coordinates','lon lat') 27514 27515 newvar = onewnc.createVariable('gridin','i',('coord', 'gridin', 'lat', 'lon')) 27516 newvar[:] = Ngridsin 27517 basicvardef(newvar,'gridin',"coordinates of the grids cells grom 'get' laying "+ \ 27513 newvar.setncattr('coordinates','lon lat') 27514 27515 innewvar = onewnc.createVariable('gridin','i',('coord', 'gridin', 'lat', 'lon')) 27516 basicvardef(innewvar,'gridin',"coordinates of the grids cells grom 'get' laying "+ \ 27518 27517 "within 'ref'",'-') 27519 newavr.setncattr('coordinates','lon lat') 27520 27521 newvar = onewnc.createVariable('gridpercen','i',('coord', 'gridin', 'lat', 'lon')) 27522 newvar[:] = percens 27523 basicvardef(newvar,'gridpercen',"percentages of the grids cells grom 'get' " + \ 27518 innewvar.setncattr('coordinates','lon lat') 27519 27520 pnewvar = onewnc.createVariable('gridpercen','f',('gridin', 'lat', 'lon')) 27521 basicvardef(pnewvar,'gridpercen',"percentages of the grids cells grom 'get' " + \ 27524 27522 "laying within 'ref'", '1') 27525 newavr.setncattr('coordinates','lon lat') 27523 pnewvar.setncattr('coordinates','lon lat') 27524 for j in range(refdy): 27525 for i in range(refdx): 27526 innewvar[:,0:Ngridsin[j,i],j,i] = gridsin[:,0:Ngridsin[j,i],j,i] 27527 pnewvar[0:Ngridsin[j,i],j,i] = percens[0:Ngridsin[j,i],j,i] 27528 onewnc.sync() 27526 27529 27527 27530 # Getting values 27531 if variable == 'all': 27532 variables = oncget.variables.keys() 27533 else: 27534 if variable.count(',') == 0: variables = [variable] 27535 else: variables = variable.split(',') 27536 27537 # Removing variables 27538 varns = '' 27539 for vn in variables: 27540 if not oncget.variables.has_key(vn): 27541 print errormsg 27542 print ' ' + fname + ": get file '" + netcdfgetn + "' does not have " + \ 27543 "variable '" + vn + "' !!" 27544 varns0 = list(oncget.variables.keys()) 27545 varns0.sort() 27546 print ' available ones:', varns0 27547 quit(-1) 27548 27549 ovar = oncget.variables[vn] 27550 vardims = ovar.dimensions 27551 if not searchInlist(vardims, getdimxn) or searchInlist(vardims, getdimyn): 27552 print ' ' + fname + ": get variable '" + vn + "' does not have space "+ \ 27553 " dimensions '" + getdimxn + "', '" + getdimxn + "' not using it !!" 27554 print " variables' dimensions:", vardims 27555 else: 27556 varns.append(vn) 27557 27558 for vn in varns: 27559 ovar = onget.variables[vn] 27560 27528 27561 27529 27562 add_global_PyNCplot(onewnc, 'nc_var_tools', fname, '1.0') 27563 27564 print fname + ": Successfull witting of file '" + ofilen + "' !!" 27530 27565 27531 27566 return
Note: See TracChangeset
for help on using the changeset viewer.