Changeset 2528 in lmdz_wrf


Ignore:
Timestamp:
May 11, 2019, 8:29:23 PM (6 years ago)
Author:
lfita
Message:

Adding look for coincidence of the faces of the grid and the polygon in `grid_within_polygon'

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/module_scientific.f90

    r2526 r2528  
    49364936
    49374937! Local
    4938     INTEGER                                              :: ix, iy, iv
    4939     REAL(r_k), DIMENSION(2)                              :: centergrid, vertex
     4938    INTEGER                                              :: ix, iy, iv, ivA
     4939    INTEGER                                              :: cross
     4940    REAL(r_k), DIMENSION(2)                              :: centergrid, vertex, crosspoint
     4941    REAL(r_k), DIMENSION(2,2)                            :: face, faceA
    49404942    LOGICAL, DIMENSION(dx,dy)                            :: within
    49414943
    49424944!!!!!!! Variables
    4943 ! NvertexA: Number of vertices of the polygin to find the grids
     4945! NvertexA: Number of vertices of the polygon to find the grids
    49444946! polygonA: ordered vertices of the polygon
    49454947! dx, dy: shape of the matrix with the grid points
     
    49564958    gridsin = 0
    49574959    within = .FALSE.
     4960
    49584961    DO ix = 1, dx
    49594962      DO iy = 1, dy
     
    49874990          END DO
    49884991
     4992          ! Getting grid faces
     4993          DO iv=1, Nvertexmax-1
     4994            IF (.NOT.within(ix,iy)) THEN
     4995              IF (xBvals(ix,iy,iv) /= fillvalI) THEN
     4996                face(1,:) = (/ xBvals(ix,iy,iv), yBvals(ix,iy,iv) /)
     4997                face(2,:) = (/ xBvals(ix,iy,iv+1), yBvals(ix,iy,iv+1) /)
     4998                DO ivA=1, NvertexA-1
     4999                  faceA(1,:) = (/ polygonA(ivA,1), polygonA(ivA,2) /)
     5000                  faceA(2,:) = (/polygonA(ivA+1,1), polygonA(ivA+1,2) /)
     5001                  CALL intersectfaces(face, faceA, cross, crosspoint)
     5002                  IF (cross /= 0) THEN
     5003                    Ngridsin = Ngridsin + 1
     5004                    ! Getting coordinates
     5005                    gridsin(Ngridsin,1) = ix
     5006                    gridsin(Ngridsin,2) = iy
     5007                    within(ix,iy) = .TRUE.
     5008                    CYCLE
     5009                  END IF
     5010                END DO
     5011                IF (.NOT.within(ix,iy)) THEN
     5012                  faceA(1,:) = (/ polygonA(NvertexA,1), polygonA(NvertexA,2) /)
     5013                  faceA(2,:) = (/polygonA(1,1), polygonA(1,2) /)
     5014                  CALL intersectfaces(face, faceA, cross, crosspoint)
     5015                  IF (cross /= 0) THEN
     5016                    Ngridsin = Ngridsin + 1
     5017                    ! Getting coordinates
     5018                    gridsin(Ngridsin,1) = ix
     5019                    gridsin(Ngridsin,2) = iy
     5020                    within(ix,iy) = .TRUE.
     5021                  END IF
     5022                END IF
     5023              END IF
     5024            END IF
     5025          END DO
     5026          iv = Nvertexmax
     5027          IF (.NOT.within(ix,iy)) THEN
     5028            IF (xBvals(ix,iy,iv) /= fillvalI) THEN
     5029              face(1,:) = (/ xBvals(ix,iy,iv), yBvals(ix,iy,iv) /)
     5030              face(2,:) = (/ xBvals(ix,iy,1), yBvals(ix,iy,1) /)
     5031              DO ivA=1, NvertexA-1
     5032                faceA(1,:) = (/ polygonA(ivA,1), polygonA(ivA,2) /)
     5033                faceA(2,:) = (/polygonA(ivA+1,1), polygonA(ivA+1,2) /)
     5034                CALL intersectfaces(face, faceA, cross, crosspoint)
     5035                IF (cross /= 0) THEN
     5036                  Ngridsin = Ngridsin + 1
     5037                  ! Getting coordinates
     5038                  gridsin(Ngridsin,1) = ix
     5039                  gridsin(Ngridsin,2) = iy
     5040                  within(ix,iy) = .TRUE.
     5041                  CYCLE
     5042                END IF
     5043              END DO
     5044              IF (.NOT.within(ix,iy)) THEN
     5045                faceA(1,:) = (/ polygonA(NvertexA,1), polygonA(NvertexA,2) /)
     5046                faceA(2,:) = (/polygonA(1,1), polygonA(1,2) /)
     5047                CALL intersectfaces(face, faceA, cross, crosspoint)
     5048                IF (cross /= 0) THEN
     5049                  Ngridsin = Ngridsin + 1
     5050                  ! Getting coordinates
     5051                  gridsin(Ngridsin,1) = ix
     5052                  gridsin(Ngridsin,2) = iy
     5053                  within(ix,iy) = .TRUE.
     5054                END IF
     5055              END IF
     5056            END IF
     5057          END IF
    49895058        END IF
    49905059      END DO
Note: See TracChangeset for help on using the changeset viewer.