Changeset 2268 in lmdz_wrf for trunk/tools
- Timestamp:
- Dec 26, 2018, 11:16:17 PM (6 years ago)
- Location:
- trunk/tools
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/tools/module_scientific.f90
r2267 r2268 4941 4941 IMPLICIT NONE 4942 4942 4943 INTEGER, INTENT(in) :: dxA, dyA, NAvertex Ama, dxB, dyB, &4943 INTEGER, INTENT(in) :: dxA, dyA, NAvertexmax, dxB, dyB, & 4944 4944 NBvertexmax, dxyB 4945 4945 REAL(r_k), DIMENSION(dxA,dyA), INTENT(in) :: xCAvals, yCAvals … … 4950 4950 INTEGER, DIMENSION(dxA,dyA), INTENT(out) :: Ngridsin 4951 4951 INTEGER, DIMENSION(dxA,dyA,dxyB,2), INTENT(out) :: gridsin 4952 REAL(r_k), DIMENSION(dxA,dyA, Ngridsin), INTENT(out):: percentages4952 REAL(r_k), DIMENSION(dxA,dyA,dxyB), INTENT(out) :: percentages 4953 4953 4954 4954 ! Local 4955 4955 INTEGER :: iv, ix, iy 4956 4956 INTEGER :: Nvertex, NvertexAgrid, Ncoin, Nsort 4957 INTEGER, ALLOCATABLE, DIMENSION(:,:) :: poinsin 4957 4958 CHARACTER(len=20) :: DS 4958 4959 REAL(r_k) :: areapoly, areagpoly, totarea, totpercent 4959 REAL(r_k), ALLOCATABLE, DIMENSION(:,:) :: vertexgrid , poinsin4960 REAL(r_k), ALLOCATABLE, DIMENSION(:,:) :: vertexgrid 4960 4961 4961 4962 !!!!!!! Variables … … 4975 4976 fname = 'spacepercen' 4976 4977 4977 DO ix = 1, d imxA4978 DO iy = 1, d imyA4978 DO ix = 1, dxA 4979 DO iy = 1, dyA 4979 4980 4980 4981 ! Getting grid vertices … … 4990 4991 vertexgrid(:,2) = yBAvals(ix,iy,1:Nvertex) 4991 4992 4992 CALL grid_within_polygon(Nvertex, vertexgrid, dxB, dyB, dxB*dyB, x BCvals, yBCvals, NBvertexmax, &4993 CALL grid_within_polygon(Nvertex, vertexgrid, dxB, dyB, dxB*dyB, xCBvals, yCBvals, NBvertexmax, & 4993 4994 xBBvals, yBBvals, Ngridsin(ix,iy), gridsin(ix,iy,:,:)) 4994 IF (ALLOCATE (poinsin)) DEALLOCATE(poinsin)4995 IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin) 4995 4996 ALLOCATE(poinsin(Ngridsin(ix,iy),2)) 4996 4997 4997 4998 DO iv=1, Ngridsin(ix,iy) 4998 poinsin(i ,1) = gridsin(ix,iy,iv,1)4999 poinsin(i ,2) = gridsin(ix,iy,iv,2)4999 poinsin(iv,1) = gridsin(ix,iy,iv,1) 5000 poinsin(iv,2) = gridsin(ix,iy,iv,2) 5000 5001 END DO 5001 5002 … … 5006 5007 END DO 5007 5008 5009 END SUBROUTINE spacepercen 5010 5008 5011 END MODULE module_scientific -
trunk/tools/nc_var_tools.py
r2267 r2268 27340 27340 ovarybnds = oncref.variables[refvarybndsn] 27341 27341 27342 refvarx, dims = SliceVarDict(ovarx,slicedict) 27343 refvarbndsx, dims = SliceVarDict(ovarxbnds,slicedict) 27344 refvary, dims = SliceVarDict(ovary,slicedict) 27345 refvarbndsy, dims = SliceVarDict(ovarybnds,slicedict) 27346 27347 reflon, reflat = gen.lonlat2D(refvarx, refvary) 27342 srefvarx, dims = SliceVarDict(ovarx,slicedict) 27343 srefvarbndsx, dims = SliceVarDict(ovarxbnds,slicedict) 27344 srefvary, dims = SliceVarDict(ovary,slicedict) 27345 srefvarbndsy, dims = SliceVarDict(ovarybnds,slicedict) 27346 27347 reflon, reflat = gen.lonlat2D(ovarx[tuple(srefvarx)], ovary[tuple(srefvary)]) 27348 refvarbndsx = ovarxbnds[tuple(srefvarbndsx)] 27349 refvarbndsy = ovarybnds[tuple(srefvarbndsy)] 27350 27348 27351 refdx = reflon.shape[1] 27349 27352 refdy = reflon.shape[0] 27350 refmaxvert = refvar xbnds.shape[2]27353 refmaxvert = refvarbndsx.shape[2] 27351 27354 27352 27355 else: … … 27439 27442 ovary = oncget.variables[getvaryn] 27440 27443 27441 getvarx, dims = SliceVarDict(ovarx,slicedict) 27442 getvarxbnds, dims = SliceVarDict(ovarxbnds,slicedict) 27443 getvary, dims = SliceVarDict(ovary,slicedict) 27444 getvarybnds, dims = SliceVarDict(ovarybnds,slicedict) 27445 27446 getlon, getlat = gen.lonlat2D(getvarx, getvary) 27444 sgetvarx, dims = SliceVarDict(ovarx,slicedict) 27445 sgetvarbndsx, dims = SliceVarDict(ovarxbnds,slicedict) 27446 sgetvary, dims = SliceVarDict(ovary,slicedict) 27447 sgetvarbndsy, dims = SliceVarDict(ovarybnds,slicedict) 27448 27449 getlon, getlat = gen.lonlat2D(ovarx[tuple(sgetvarx)], ovary[tuple(sgetvary)]) 27450 getvarbndsx = ovarxbnds[tuple(sgetvarbndsx)] 27451 getvarbndsy = ovarybnds[tuple(sgetvarbndsy)] 27447 27452 getdx = getlon.shape[1] 27448 27453 getdy = getlon.shape[0] 27449 getmaxvert = getvar xbnds.shape[2]27454 getmaxvert = getvarbndsx.shape[2] 27450 27455 27451 27456 iif = iif + 1 … … 27453 27458 reflont = reflon.transpose() 27454 27459 reflatt = reflat.transpose() 27455 refvarxbndst = refvar xbnds.transpose()27456 refvarybndst = refvar ybnds.transpose()27460 refvarxbndst = refvarbndsx.transpose() 27461 refvarybndst = refvarbndsy.transpose() 27457 27462 getlont = getlon.transpose() 27458 27463 getlatt = getlat.transpose() 27459 getvarxbndst = getvar xbnds.transpose()27460 getvarybndst = getvar ybnds.transpose()27464 getvarxbndst = getvarbndsx.transpose() 27465 getvarybndst = getvarbndsy.transpose() 27461 27466 27462 27467 Ngridsint, gridsint, percenst = fsci.module_scientific.spacepercen(dxa=refdx, \ 27463 dya=refdy, xcavals=reflont, ycavals=reflatt, navertmax=refmaxvert, \ 27464 xbAvals=refvarxbndst, ybAvals=refvarybndst, \ 27465 dxb=getdx, dyb=getdy, xcbvals=getlont, ycbvals=getlatt, nbvertmax=getmaxvert, \ 27466 xbbvals=getvarxbndst, ybbvals=getvarybndst, strict=strict) 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) 27467 27473 27468 27474 Ngridsin = Ngridint.transpose()
Note: See TracChangeset
for help on using the changeset viewer.