| 1 | PROGRAM trajectories_overlap |
|---|
| 2 | ! Porgram to compute trajectories from a series of consecutive maps of polygons |
|---|
| 3 | ! L. Fita, CIMA. September 2017 |
|---|
| 4 | ! |
|---|
| 5 | ! To be used with a netcdf file which must contain: |
|---|
| 6 | ! - Series of 2D maps of polygons (numbered by integers) |
|---|
| 7 | ! - Areal weighted centers of the polygons |
|---|
| 8 | ! - Weighted areas of the polygons |
|---|
| 9 | ! |
|---|
| 10 | |
|---|
| 11 | USE module_definitions |
|---|
| 12 | USE module_generic |
|---|
| 13 | USE module_NCgeneric |
|---|
| 14 | USE module_scientific |
|---|
| 15 | USE netcdf |
|---|
| 16 | |
|---|
| 17 | IMPLICIT NONE |
|---|
| 18 | |
|---|
| 19 | ! namelist |
|---|
| 20 | INTEGER :: missing_value |
|---|
| 21 | REAL(r_k) :: minarea |
|---|
| 22 | CHARACTER(len=50) :: polyfilename |
|---|
| 23 | CHARACTER(len=50) :: poly2Dn, polyNn, polywctrn, polywarean, & |
|---|
| 24 | varnresx, varnresy, timen, projectn, waycomp, waymulti |
|---|
| 25 | LOGICAL :: debug |
|---|
| 26 | |
|---|
| 27 | ! Local |
|---|
| 28 | INTEGER :: funit, ncunit, rcode |
|---|
| 29 | INTEGER :: ierr, ios |
|---|
| 30 | INTEGER :: Nvdims |
|---|
| 31 | INTEGER, DIMENSION(1) :: dims1D |
|---|
| 32 | INTEGER, DIMENSION(2) :: dims2D |
|---|
| 33 | INTEGER, DIMENSION(3) :: dims3D |
|---|
| 34 | INTEGER, DIMENSION(:), ALLOCATABLE :: polyN |
|---|
| 35 | INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: polys |
|---|
| 36 | REAL(r_k) :: resx, resy |
|---|
| 37 | REAL(r_k), DIMENSION(:,:), ALLOCATABLE :: polyas |
|---|
| 38 | REAL(r_k), DIMENSION(:,:,:), ALLOCATABLE :: polywctrs |
|---|
| 39 | LOGICAL :: gotvar |
|---|
| 40 | CHARACTER(len=3) :: num3S |
|---|
| 41 | INTEGER :: dimx, dimy, dimt, Ncoord, Nmaxpoly, & |
|---|
| 42 | Nmaxtrack |
|---|
| 43 | |
|---|
| 44 | NAMELIST /files/ polyfilename, poly2Dn, polyNn, polywctrn, polywarean, varnresx, varnresy, timen |
|---|
| 45 | NAMELIST /config/ missing_value, minarea, projectn, waycomp, waymulti, debug |
|---|
| 46 | |
|---|
| 47 | !!!!!!! |
|---|
| 48 | ! polyfilename: name of the file with the polygon information |
|---|
| 49 | ! poly2Dn: name of the variable with the maps of 2D polygons |
|---|
| 50 | ! polyNn: name of the variable with the number of 2D polygons per time-step |
|---|
| 51 | ! polywctrn: name of the varibale with the coordinates of the weighted centers of all the polygons |
|---|
| 52 | ! polywarean: name of the variable with the weighted areas of the polygons |
|---|
| 53 | ! varnres[x/y]: name of the variable with the resolution along x an y axis (same units as polywarean) |
|---|
| 54 | ! lonn: name of the variable with the longitudes |
|---|
| 55 | ! latn: name of the variable with the latitudes |
|---|
| 56 | ! timen: name of the variable with the times |
|---|
| 57 | ! missing_value: value to determine the missing value |
|---|
| 58 | ! minarea: minimal area of the polygons to determine which polygons to use |
|---|
| 59 | ! projectn: name of the projection of the data in the file. Available ones: |
|---|
| 60 | ! 'ctsarea': Constant Area |
|---|
| 61 | ! 'lon/lat': for regular longitude-latitude |
|---|
| 62 | ! 'nadir-sat,[lonNADIR],[latNADIR]': for satellite data with the resolution given at nadir (lonNADIR, latNADIR) |
|---|
| 63 | ! waycomp: how to copmute when intermediate ASCII files are used |
|---|
| 64 | ! 'scratch': everything from the beginning |
|---|
| 65 | ! 'continue': skipt that parts which already have the ascii file written |
|---|
| 66 | ! waymulti: methodology to follow when multiple polygons are given for the same track |
|---|
| 67 | ! 'mean': get coordinates from the areal-weighted mean of the centers of the given polygons and their areas |
|---|
| 68 | ! 'largest': get the coorindates of the largest polygon |
|---|
| 69 | ! 'closest': get the coordinates of the closest polygon |
|---|
| 70 | |
|---|
| 71 | fname = 'trajectories_overlap' |
|---|
| 72 | |
|---|
| 73 | ! Reading namelist |
|---|
| 74 | funit = freeunit() |
|---|
| 75 | OPEN(funit, file='trajectories_overlap.namelist', status='old', form='formatted', iostat=ios) |
|---|
| 76 | msg = "Problems reading nameslit file: 'trajectories_overlap.namelist'" |
|---|
| 77 | CALL ErrMsg(msg, 'main', ios) |
|---|
| 78 | |
|---|
| 79 | READ(funit, files) |
|---|
| 80 | READ(funit, config) |
|---|
| 81 | CLOSE(funit) |
|---|
| 82 | |
|---|
| 83 | ! Opening polygon file |
|---|
| 84 | rcode = nf90_open(TRIM(polyfilename), NF90_NOWRITE, ncunit) |
|---|
| 85 | IF (rcode /= NF90_NOERR) CALL handle_err(rcode) |
|---|
| 86 | |
|---|
| 87 | ! Getting variables |
|---|
| 88 | !! |
|---|
| 89 | |
|---|
| 90 | ! polygons |
|---|
| 91 | gotvar = isin_ncunit(ncunit, poly2Dn) |
|---|
| 92 | IF (.NOT.gotvar) THEN |
|---|
| 93 | msg= "File '"//TRIM(polyfilename)//"' does not have 2D polygons variable '" // TRIM(poly2Dn) // "'" |
|---|
| 94 | CALL ErrMsg(msg, fname, -1) |
|---|
| 95 | END IF |
|---|
| 96 | Nvdims = get_varNdims_ncunit(ncunit, poly2Dn) |
|---|
| 97 | IF (Nvdims /= 3) THEN |
|---|
| 98 | WRITE(num3S,'(I3)')Nvdims |
|---|
| 99 | msg = "Variable with 2D polygons '" // TRIM(poly2Dn) // "' has: " // num3S // & |
|---|
| 100 | " it must have 3 dimensions !!" |
|---|
| 101 | CALL ErrMsg(msg, fname, -1) |
|---|
| 102 | END IF |
|---|
| 103 | dims3D = get_var3dims_ncunit(ncunit, poly2Dn) |
|---|
| 104 | IF (ALLOCATED(polys)) DEALLOCATE(polys) |
|---|
| 105 | ALLOCATE(polys(dims3D(1), dims3D(2), dims3D(3)), STAT=ierr) |
|---|
| 106 | msg = "Problems allocating 'polys'" |
|---|
| 107 | CALL ErrMsg(msg, fname, ierr) |
|---|
| 108 | CALL get_varI3D_ncunit(ncunit, dims3D(1), dims3D(2), dims3D(3), poly2Dn, polys) |
|---|
| 109 | IF (debug) PRINT *," Got variable 'polys':", UBOUND(polys) |
|---|
| 110 | |
|---|
| 111 | ! Getting rid of the mising values |
|---|
| 112 | WHERE (polys == missing_value) |
|---|
| 113 | polys = 0 |
|---|
| 114 | END WHERE |
|---|
| 115 | |
|---|
| 116 | dimx = dims3D(1) |
|---|
| 117 | dimy = dims3D(2) |
|---|
| 118 | dimt = dims3D(3) |
|---|
| 119 | |
|---|
| 120 | ! N polygons |
|---|
| 121 | gotvar = isin_ncunit(ncunit, polyNn) |
|---|
| 122 | IF (.NOT.gotvar) THEN |
|---|
| 123 | msg="File '"//TRIM(polyfilename)//"' does not have number of polygons variable '" // TRIM(polyNn) & |
|---|
| 124 | // "'" |
|---|
| 125 | CALL ErrMsg(msg, fname, -1) |
|---|
| 126 | END IF |
|---|
| 127 | Nvdims = get_varNdims_ncunit(ncunit, polyNn) |
|---|
| 128 | IF (Nvdims /= 1) THEN |
|---|
| 129 | WRITE(num3S,'(I3)')Nvdims |
|---|
| 130 | msg = "Variable with N polygons '" // TRIM(polyNn) // "' has: " // num3S // & |
|---|
| 131 | " it must have 1 dimensions !!" |
|---|
| 132 | CALL ErrMsg(msg, fname, -1) |
|---|
| 133 | END IF |
|---|
| 134 | dims1D = get_var1dims_ncunit(ncunit, polyNn) |
|---|
| 135 | IF (ALLOCATED(polyN)) DEALLOCATE(polyN) |
|---|
| 136 | ALLOCATE(polyN(dims1D(1)), STAT=ierr) |
|---|
| 137 | msg = "Problems allocating 'polyN'" |
|---|
| 138 | CALL ErrMsg(msg, fname, ierr) |
|---|
| 139 | CALL get_varI1D_ncunit(ncunit, dims1D(1), polyNn, polyN) |
|---|
| 140 | IF (debug) PRINT *," Got variable 'polyN':", UBOUND(polyN) |
|---|
| 141 | |
|---|
| 142 | ! weighted-center of the polygons |
|---|
| 143 | gotvar = isin_ncunit(ncunit, polywctrn) |
|---|
| 144 | IF (.NOT.gotvar) THEN |
|---|
| 145 | msg = "File '" // TRIM(polyfilename) // "' does not have weighted-centerd polygon variable '" // & |
|---|
| 146 | TRIM(polywctrn) // "'" |
|---|
| 147 | CALL ErrMsg(msg, fname, -1) |
|---|
| 148 | END IF |
|---|
| 149 | Nvdims = get_varNdims_ncunit(ncunit, polywctrn) |
|---|
| 150 | IF (Nvdims /= 3) THEN |
|---|
| 151 | WRITE(num3S,'(I3)')Nvdims |
|---|
| 152 | msg = "Variable with weighted-centerd polygons '" // TRIM(polywctrn) // "' has: " // num3S // & |
|---|
| 153 | " it must have 3 dimensions !!" |
|---|
| 154 | CALL ErrMsg(msg, fname, -1) |
|---|
| 155 | END IF |
|---|
| 156 | dims3D = get_var3dims_ncunit(ncunit, polywctrn) |
|---|
| 157 | IF (ALLOCATED(polywctrs)) DEALLOCATE(polywctrs) |
|---|
| 158 | ALLOCATE(polywctrs(dims3D(1), dims3D(2), dims3D(3)), STAT=ierr) |
|---|
| 159 | msg = "Problems allocating 'polywctrs'" |
|---|
| 160 | CALL ErrMsg(msg, fname, ierr) |
|---|
| 161 | CALL get_varRK3D_ncunit(ncunit, dims3D(1), dims3D(2), dims3D(3), polywctrn, polywctrs) |
|---|
| 162 | IF (debug) PRINT *," Got variable 'polyectrs':", UBOUND(polywctrs) |
|---|
| 163 | Nmaxpoly = dims3D(2) |
|---|
| 164 | Ncoord = dims3D(3) |
|---|
| 165 | |
|---|
| 166 | ! area of polygons |
|---|
| 167 | gotvar = isin_ncunit(ncunit, polywarean) |
|---|
| 168 | IF (.NOT.gotvar) THEN |
|---|
| 169 | msg = "File '" // TRIM(polyfilename) // "' does not have variable '" // TRIM(polywarean) // "'" |
|---|
| 170 | CALL ErrMsg(msg, fname, -1) |
|---|
| 171 | END IF |
|---|
| 172 | Nvdims = get_varNdims_ncunit(ncunit, polywarean) |
|---|
| 173 | IF (Nvdims /= 2) THEN |
|---|
| 174 | WRITE(num3S,'(I3)')Nvdims |
|---|
| 175 | msg = "Variable with area polygons '" // TRIM(polywarean) // "' has: " // num3S // & |
|---|
| 176 | " it must have 2 dimensions !!" |
|---|
| 177 | CALL ErrMsg(msg, fname, -1) |
|---|
| 178 | END IF |
|---|
| 179 | dims2D = get_var2dims_ncunit(ncunit, polywarean) |
|---|
| 180 | IF (ALLOCATED(polyas)) DEALLOCATE(polyas) |
|---|
| 181 | ALLOCATE(polyas(dims2D(1), dims2D(2)), STAT=ierr) |
|---|
| 182 | msg = "Problems allocating 'polyas'" |
|---|
| 183 | CALL ErrMsg(msg, fname, ierr) |
|---|
| 184 | CALL get_varRK2D_ncunit(ncunit, dims2D(1), dims2D(2), polywarean, polyas) |
|---|
| 185 | IF (debug) PRINT *," Got variable 'polyas':", UBOUND(polyas) |
|---|
| 186 | |
|---|
| 187 | ! Resolution along x/y axis |
|---|
| 188 | gotvar = isin_ncunit(ncunit, varnresx) |
|---|
| 189 | IF (.NOT.gotvar) THEN |
|---|
| 190 | msg = "File '" // TRIM(polyfilename) // "' does not have variable '" // TRIM(varnresx) // "'" |
|---|
| 191 | CALL ErrMsg(msg, fname, -1) |
|---|
| 192 | END IF |
|---|
| 193 | CALL get_varRK0D_ncunit(ncunit, varnresx, resx) |
|---|
| 194 | IF (debug) PRINT *," Got variable 'resx':", resx |
|---|
| 195 | |
|---|
| 196 | gotvar = isin_ncunit(ncunit, varnresy) |
|---|
| 197 | IF (.NOT.gotvar) THEN |
|---|
| 198 | msg = "File '" // TRIM(polyfilename) // "' does not have variable '" // TRIM(varnresy) // "'" |
|---|
| 199 | CALL ErrMsg(msg, fname, -1) |
|---|
| 200 | END IF |
|---|
| 201 | CALL get_varRK0D_ncunit(ncunit, varnresy, resy) |
|---|
| 202 | IF (debug) PRINT *," Got variable 'resy':", resy |
|---|
| 203 | |
|---|
| 204 | rcode = nf90_close(ncunit) |
|---|
| 205 | IF (rcode /= NF90_NOERR) CALL handle_err(rcode) |
|---|
| 206 | |
|---|
| 207 | ! Preparing outcome (trajectories) |
|---|
| 208 | Nmaxtrack = Nmaxpoly*dimt/100 |
|---|
| 209 | |
|---|
| 210 | IF (debug) THEN |
|---|
| 211 | PRINT *,'Computing trajectories _______' |
|---|
| 212 | PRINT *,' 2D space:', dimx, ' x', dimy |
|---|
| 213 | PRINT *,' number time-steps:', dimt |
|---|
| 214 | PRINT *,' maximum number of polygons:', Nmaxpoly |
|---|
| 215 | PRINT *,' maximum number of trajectories:', Nmaxtrack |
|---|
| 216 | END IF |
|---|
| 217 | |
|---|
| 218 | ! Computing trajectories |
|---|
| 219 | CALL poly_overlap_tracks_area_ascii(debug, waycomp, dimx, dimy, dimt, minarea, polyN, polys, & |
|---|
| 220 | polywctrs, polyas, Nmaxpoly, Nmaxtrack, waymulti) |
|---|
| 221 | |
|---|
| 222 | ! Writting trajectory files |
|---|
| 223 | |
|---|
| 224 | DEALLOCATE(polys) |
|---|
| 225 | DEALLOCATE(polyN) |
|---|
| 226 | DEALLOCATE(polywctrs) |
|---|
| 227 | DEALLOCATE(polyas) |
|---|
| 228 | |
|---|
| 229 | END PROGRAM trajectories_overlap |
|---|
| 230 | |
|---|