Changeset 2270 in lmdz_wrf
- Timestamp:
- Dec 27, 2018, 7:30:13 PM (6 years ago)
- Location:
- trunk/tools
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/tools/module_scientific.f90
r2269 r2270 62 62 ! series of r_k numbers 63 63 ! SwapR_K*: Subroutine swaps the values of its two formal arguments. 64 ! unique_matrixRK2D: Subroutine to provide the unique values within a 2D RK matrix 64 65 ! write_finaltrack_ascii: Subroutine to read the final trajectories into an ASCII file 65 66 ! write_overlap_polys_ascii: Subroutine to write to an ASCII file the associated polygons at a given time-step … … 5011 5012 END SUBROUTINE spacepercen 5012 5013 5014 SUBROUTINE unique_matrixRK2D(dx, dy, dxy, matrix2D, Nunique, unique) 5015 ! Subroutine to provide the unique values within a 2D RK matrix 5016 5017 IMPLICIT NONE 5018 5019 INTEGER, INTENT(in) :: dx, dy, dxy 5020 REAL(r_k), DIMENSION(dx,dy), INTENT(in) :: matrix2D 5021 INTEGER, INTENT(out) :: Nunique 5022 REAL(r_k), DIMENSION(dxy), INTENT(out) :: unique 5023 5024 ! Local 5025 INTEGER :: ix, iy, iu, minvalv 5026 LOGICAL :: single 5027 5028 !!!!!!! Variables 5029 ! dx, dy: dimensions of the matrix 5030 ! dxy: dx*dy, maximum possible amount of different values 5031 ! matrix2D: matgrix of values 5032 ! Nunique: amount of unique values 5033 ! unique: sorted from minimum to maximum vector with the unique values 5034 5035 fname = 'unique_matrixRK2D' 5036 5037 minvalv = MINVAL(matrix2D) 5038 5039 Nunique = 1 5040 unique(1) = minvalv 5041 DO ix= 1, dx 5042 DO iy= 1, dy 5043 single = .TRUE. 5044 DO iu = 1, Nunique 5045 IF (matrix2D(ix,iy) == unique(iu)) THEN 5046 single = .FALSE. 5047 EXIT 5048 END IF 5049 END DO 5050 IF (single) THEN 5051 Nunique = Nunique + 1 5052 unique(Nunique) = matrix2D(ix,iy) 5053 END IF 5054 END DO 5055 END DO 5056 5057 CALL sortR_K(unique, Nunique) 5058 5059 END SUBROUTINE unique_matrixRK2D 5060 5013 5061 SUBROUTINE spaceweightstats(varin, Ngridsin, gridsin, percentages, stats, varout, dxA, dyA, dxB, & 5014 5062 dyB, maxNgridsin, Lstats) … … 5018 5066 5019 5067 INTEGER, INTENT(in) :: dxA, dyA, dxB, dyB, maxNgridsin, Lstats 5020 CHARACTER(len= 60), INTENT(in):: stats5068 CHARACTER(len=*), INTENT(in) :: stats 5021 5069 INTEGER, DIMENSION(dxA,dyA), INTENT(in) :: Ngridsin 5022 5070 INTEGER, DIMENSION(dxA,dyA,maxNgridsin,2), INTENT(in):: gridsin 5023 REAL(r_k), DIMENSION(dxB,dyB), INTENT( out):: varin5071 REAL(r_k), DIMENSION(dxB,dyB), INTENT(in) :: varin 5024 5072 REAL(r_k), DIMENSION(dxA,dyA,maxNgridsin), INTENT(in):: percentages 5025 5073 REAL(r_k), DIMENSION(dxA,dyA,Lstats), INTENT(out) :: varout 5026 5074 5027 5075 ! Local 5028 INTEGER :: ix, iy, iv, ii, jj 5076 INTEGER :: ix, iy, iv, ic, iu, ii, jj 5077 INTEGER :: Ncounts 5078 CHARACTER(len=3) :: val1S, val2S 5079 CHARACTER(len=30) :: val3S 5080 REAL(r_k) :: val1, val2 5081 REAL(r_k), DIMENSION(Lstats) :: icounts 5029 5082 5030 5083 !!!!!!! Variables … … 5041 5094 ! 'min': minimum value 5042 5095 ! 'max': maximum value 5043 ! 'mean': mean value5044 ! 'mean2': quadratic mean value5045 ! 'stddev': s tandard deviation value5096 ! 'mean': space weighted mean value 5097 ! 'mean2': space weighted quadratic mean value 5098 ! 'stddev': space weighted standard deviation value 5046 5099 ! 'count': percentage of the space of matrix A covered by each different value of matrix B 5047 5100 ! varout: output statistical variable … … 5062 5115 END DO 5063 5116 END DO 5117 CASE('max') 5118 varout = -fillVal64 5119 DO ix=1, dxA 5120 DO iy=1, dyA 5121 DO iv=1, Ngridsin(ix,iy) 5122 ii = gridsin(ix,iy,iv,1) 5123 jj = gridsin(ix,iy,iv,2) 5124 IF (varin(ii,jj) > varout(ix,iy,Lstats)) varout(ix,iy,1) = varin(ii,jj) 5125 END DO 5126 END DO 5127 END DO 5128 CASE('mean') 5129 varout = zeroRK 5130 DO ix=1, dxA 5131 DO iy=1, dyA 5132 DO iv=1, Ngridsin(ix,iy) 5133 ii = gridsin(ix,iy,iv,1) 5134 jj = gridsin(ix,iy,iv,2) 5135 varout(ix,iy,1) = varout(ix,iy,1) + varin(ii,jj)*percentages(ix,iy,iv) 5136 END DO 5137 END DO 5138 END DO 5139 CASE('mean2') 5140 varout = zeroRK 5141 DO ix=1, dxA 5142 DO iy=1, dyA 5143 DO iv=1, Ngridsin(ix,iy) 5144 ii = gridsin(ix,iy,iv,1) 5145 jj = gridsin(ix,iy,iv,2) 5146 varout(ix,iy,1) = varout(ix,iy,1) + percentages(ix,iy,iv)*(varin(ii,jj))**2 5147 END DO 5148 varout(ix,iy,1) = varout(ix,iy,1) / Ngridsin(ix,iy) 5149 END DO 5150 END DO 5151 CASE('stddev') 5152 varout = zeroRK 5153 DO ix=1, dxA 5154 DO iy=1, dyA 5155 val1 = zeroRK 5156 val2 = zeroRK 5157 DO iv=1, Ngridsin(ix,iy) 5158 ii = gridsin(ix,iy,iv,1) 5159 jj = gridsin(ix,iy,iv,2) 5160 val1 = val1 + varin(ii,jj)*percentages(ix,iy,iv) 5161 val2 = val2 + percentages(ix,iy,iv)*(varin(ii,jj))**2 5162 END DO 5163 varout(ix,iy,1) = SQRT(val2 - val1**2) 5164 END DO 5165 END DO 5166 CASE('count') 5167 CALL unique_matrixRK2D(dxA, dyA, dxA*dyA, varin, Ncounts, icounts) 5168 IF (Lstats /= Ncounts) THEN 5169 WRITE(val1S,'(I3)')Lstats 5170 WRITE(val2S,'(I3)')Ncounts 5171 msg = "for 'count' different amount of passed categories: " // TRIM(val1S) // & 5172 ' and found ' // TRIM(val2S) 5173 CALL ErrMsg(msg, fname, -1) 5174 END IF 5175 varout = zeroRK 5176 DO ix=1, dxA 5177 DO iy=1, dyA 5178 DO iv=1, Ngridsin(ix,iy) 5179 ii = gridsin(ix,iy,iv,1) 5180 jj = gridsin(ix,iy,iv,2) 5181 ic = Index1DArrayR_K(icounts, Ncounts, varin(ii,jj)) 5182 IF (ic == -1) THEN 5183 WRITE(val3S,'(f30.20)')varin(ii,jj) 5184 msg = "value '" // val3S // "' for 'count' not found" 5185 CALL ErrMSg(msg, fname, -1) 5186 ELSE 5187 varout(ix,iy,ic) = varout(ix,iy,ic) + percentages(ix,iy,iv) 5188 END IF 5189 END DO 5190 END DO 5191 END DO 5064 5192 CASE DEFAULT 5065 5193 msg = "statisitcs '" // TRIM(stats) // "' not ready !!" // CHAR(44) // " available ones: " // & -
trunk/tools/nc_var_tools.py
r2269 r2270 27186 27186 [stats]: ',' separated list of space-statistics within each `ref' grid to 27187 27187 provide for each grid cell from the 'get' data 27188 'm ean': weghted mean (always provided)27189 'm in': minimum value and is associated weight27190 'm ax': maximum value and is associated weight27191 'mean2': we ghted quadratic mean27188 'min': minimum value 27189 'max': maximum value 27190 'mean': weighted mean 27191 'mean2': weighted quadratic mean 27192 27192 'stddev': standard deviation 27193 'count': percentage of the space of matrix `ref' covered by each different 27194 value of matrix `get' 27193 27195 [ncfiles]= ',' separated list of [netcdfref]:[dimvalsref],[netcdfget]:[dimvalsget] 27194 27196 [netcdfref]: netCDF file name to be used as reference or destination … … 27221 27223 27222 27224 statsavail = ['mean', 'min', 'max', 'mean2', 'stddev'] 27225 # Characteristics of the statistics 27226 statnschars = {'mean': ['spcmean', 'spatial mean', 1], \ 27227 'min': ['spcmin', 'spatial minimum', 1], \ 27228 'max': ['spcmax', 'spatial maximum', 1], \ 27229 'mean2': ['spc2mean', 'spatial quadratic mean', 1], \ 27230 'stddev': ['spcstddev', 'spatial standard deviation', 1], \ 27231 'count': ['spccount', 'spatial coverage by value', 1]} 27223 27232 27224 27233 expectargs = '[strict]:[stats]' … … 27226 27235 27227 27236 strict = gen.Str_Bool(values.split(':')[0]) 27228 stat s = values.split(':')[1].split(',')27229 27230 for stn in stat s:27237 statns = gen.str_list(values.split(':')[1], ',') 27238 27239 for stn in statns: 27231 27240 if not gen.searchInlist(statsavail, stn): 27232 27241 print errormsg 27233 27242 print ' ' + fname + ": statistics '" + stn + "' not ready !!" 27234 print ' available ones:', stat savail27243 print ' available ones:', statnschar.keys() 27235 27244 quit(-1) 27236 27245 … … 27437 27446 quit(-1) 27438 27447 27439 slicedict = {getdimxn: slicedimx, getdimyn: slicedimy}27448 getslicedict = {getdimxn: slicedimx, getdimyn: slicedimy} 27440 27449 ovarx = oncget.variables[getvarxn] 27441 27450 ovarxbnds = oncget.variables[getvarxbndsn] … … 27443 27452 ovarybnds = oncget.variables[getvarybndsn] 27444 27453 27445 sgetvarx, dims = SliceVarDict(ovarx, slicedict)27446 sgetvarbndsx, dims = SliceVarDict(ovarxbnds, slicedict)27447 sgetvary, dims = SliceVarDict(ovary, slicedict)27448 sgetvarbndsy, dims = SliceVarDict(ovarybnds, slicedict)27454 sgetvarx, dims = SliceVarDict(ovarx,getslicedict) 27455 sgetvarbndsx, dims = SliceVarDict(ovarxbnds,getslicedict) 27456 sgetvary, dims = SliceVarDict(ovary,getslicedict) 27457 sgetvarbndsy, dims = SliceVarDict(ovarybnds,getslicedict) 27449 27458 27450 27459 getlon, getlat = gen.lonlat2D(ovarx[tuple(sgetvarx)], ovary[tuple(sgetvary)]) … … 27476 27485 percens = percenst.transpose() 27477 27486 27487 Ngridsinmax = np.max(Ngridsin) 27488 27478 27489 # Opening new file 27479 27490 ofilen = fname + '.nc' … … 27484 27495 newdim = onewnc.createDimension('lat',refdy) 27485 27496 newdim = onewnc.createDimension('bnds',refmaxvert) 27486 newdim = onewnc.createDimension('gridin', np.max(Ngridsin))27497 newdim = onewnc.createDimension('gridin',Ngridsinmax) 27487 27498 newdim = onewnc.createDimension('coord',2) 27488 27499 … … 27509 27520 newvar = onewnc.createVariable('Ngrid','i',('lat','lon')) 27510 27521 newvar[:] = Ngridsin[:] 27511 basicvardef(newvar, 'Ngrid', "number of grids cells grom 'get'laying within" + \27512 " 'ref'",'-')27522 basicvardef(newvar, 'Ngrid', "number of grids cells from .get. laying within" + \ 27523 " .ref.",'-') 27513 27524 newvar.setncattr('coordinates','lon lat') 27514 27525 27515 27526 innewvar = onewnc.createVariable('gridin','i',('coord', 'gridin', 'lat', 'lon')) 27516 basicvardef(innewvar,'gridin',"coordinates of the grids cells grom 'get'laying "+ \27517 "within 'ref'",'-')27527 basicvardef(innewvar,'gridin',"coordinates of the grids cells from .get. laying "+ \ 27528 "within .ref.",'-') 27518 27529 innewvar.setncattr('coordinates','lon lat') 27519 27530 27520 27531 pnewvar = onewnc.createVariable('gridpercen','f',('gridin', 'lat', 'lon')) 27521 basicvardef(pnewvar,'gridpercen',"percentages of the grids cells grom 'get'" + \27522 "laying within 'ref'", '1')27532 basicvardef(pnewvar,'gridpercen',"percentages of the grids cells from .get. " + \ 27533 "laying within .ref.", '1') 27523 27534 pnewvar.setncattr('coordinates','lon lat') 27524 27535 for j in range(refdy): … … 27528 27539 onewnc.sync() 27529 27540 27541 # Getting the right sizes 27542 gridsin = innewvar[:] 27543 gridsint = gridsin.transpose() 27544 percens = pnewvar[:] 27545 percenst = percens.transpose() 27546 27530 27547 # Getting values 27531 27548 if variable == 'all': … … 27536 27553 27537 27554 # Removing variables 27538 varns = ''27555 varns = [] 27539 27556 for vn in variables: 27540 27557 if not oncget.variables.has_key(vn): … … 27549 27566 ovar = oncget.variables[vn] 27550 27567 vardims = ovar.dimensions 27551 if not searchInlist(vardims, getdimxn) or searchInlist(vardims, getdimyn): 27568 if not gen.searchInlist(vardims, getdimxn) or \ 27569 not gen.searchInlist(vardims, getdimyn): 27552 27570 print ' ' + fname + ": get variable '" + vn + "' does not have space "+ \ 27553 " dimensions '" + getdimxn + "', '" + getdim xn + "' not using it !!"27571 " dimensions '" + getdimxn + "', '" + getdimyn + "' not using it !!" 27554 27572 print " variables' dimensions:", vardims 27555 27573 else: … … 27557 27575 27558 27576 for vn in varns: 27559 ovar = onget.variables[vn] 27560 27577 print ' ' + fname + ": using '" + vn + "' ..." 27578 ovar = oncget.variables[vn] 27579 svar, dimvar = SliceVarDict(ovar,getslicedict) 27580 varvals = ovar[tuple(svar)] 27581 27582 varvalst = varvals.transpose() 27583 27584 for stn in statns: 27585 print " computing '" + stn + "' " 27586 statchar = statnschars[stn] 27587 27588 if stn == 'count': 27589 svals = np.unique(varin) 27590 statchar[2] = len(svals) 27591 27592 varout = fsci.module_scientific.spaceweightstats(varin=varvalst, \ 27593 ngridsin=Ngridsint, gridsin=gridsint, percentages=percenst, \ 27594 stats=stn, dxa=refdx, dya=refdy, dxb=getdx, dyb=getdy, \ 27595 maxngridsin=Ngridsinmax, lstats=statchar[2]) 27596 27597 varout = varout.transpose() 27598 if statchar[2] == 1: 27599 newvar = onewnc.createVariable(vn + statchar[0], 'f', ('lat','lon')) 27600 newvar[:] = varout[0,:,:] 27601 else: 27602 if stn == 'count': 27603 if not gen.searchInlist(onewnc.dimensions, 'count'): 27604 newdim = onewnc.createDimension('count', statchar[2]) 27605 newvar = onewnc.createVariable(vn + 'count', 'f', ('count')) 27606 newvar[:] = svals 27607 basicvardef(newvar, vn+'count', 'unique .get. values of ' + \ 27608 vn, ovar.units) 27609 27610 newvar = onewnc.createVariable(vn + statchar[0], 'f', ('count', \ 27611 'lat','lon')) 27612 newvar[:] = varout[:] 27613 basicvardef(newvar, vn + statchar[0], vn + ' ' + statchar[1] + " from "+ \ 27614 " .get. values", ovar.units) 27615 newvar.setncattr('coordinates','lon lat') 27616 onewnc.sync() 27561 27617 27562 27618 add_global_PyNCplot(onewnc, 'nc_var_tools', fname, '1.0') 27619 onewnc.setncattr('ref_file',netcdfrefn) 27620 onewnc.setncattr('get_file',netcdfgetn) 27621 27622 onewnc.sync() 27623 onewnc.close() 27563 27624 27564 27625 print fname + ": Successfull witting of file '" + ofilen + "' !!" … … 27567 27628 27568 27629 fvals= 'reference_data.nc:lon;lon;lon_bnds;-1;lat;lat;lat_bnds;-1,get_data.nc:lon;lon;lon_bnds;-1;lat;lat;lat_bnds;-1' 27569 area_weighted('yes:m ean,min,max',fvals,'ct_values')27630 area_weighted('yes:min,max,mean,stddev',fvals,'ct_values') 27570 27631 27571 27632
Note: See TracChangeset
for help on using the changeset viewer.