source: lmdz_wrf/trunk/tools/module_scientific.f90 @ 2347

Last change on this file since 2347 was 2345, checked in by lfita, 6 years ago

Adding right filling value in variable `range' after homogenization

File size: 254.2 KB
Line 
1MODULE module_scientific
2! Module of the scientific function/subroutines
3 
4!!!!!!! Functions & subroutines
5! all_polygons_properties: Subroutine to determine the properties of all polygons in a 2D field:
6! borders_matrixL: Subroutine to provide the borders of a logical array (interested in .TRUE.)
7! coincidence_all_polys: Subtourine to determine which is the coincident polygon when a boolean polygon is provided
8!   to a map of integer polygons
9! coincidence_all_polys_area: Subtourine to determine which is the coincident polygon when a boolean polygon is provided
10!   to a map of integer polygons filtrered by a minimal area
11! coincidence_poly: Subtourine to determine which is the coincident polygon when a boolean polygon is provided
12!   to a map of integer polygons
13! coincidence_poly_area: Subtourine to determine which is the coincident polygon when a boolean polygon is provided
14!   to a map of integer polygons filtrered by a minimal area
15! coincident_gridsin2D: Subroutine to determine which lists of 2D gridsin points of an A list are also found in a B list
16! coincident_list_2Dcoords: Subroutine to determine which 2D points of an A list are also found in a B list
17! clean_polygons: Subroutine to clean polygons from non-used paths, polygons only left as path since they are inner path of a hole
18! coincident_polygon: Subroutine to provide the intersection polygon between two polygons
19! distanceRK: Function to provide the distance between two points
20! FindMinimumR_K*: Function returns the location of the minimum in the section between Start and End.
21! fill3DI_2Dvec: Subroutine to fill a 3D integer matrix from a series of indices from a 2D matrix
22! fill3DR_2Dvec: Subroutine to fill a 3D float matrix from a series of indices from a 2D matrix
23! grid_within_polygon: Subroutine to determine which grid cells from a matrix lay inside a polygon
24! grid_spacepercen: Subroutine to compute the space-percentages of a series of grid cells (B) which lay inside another
25!   series of grid-cells (A)
26! grid_spacepercen_providing_polys: Subroutine to compute the space-percentages of a series of grid cells (B) which lay inside another
27!   series of grid-cells (A) providing coincident polygons
28! grid_spacepercen_within_reg: Subroutine to compute the percentage of grid space of a series of grid cells which are encompassed
29!   by a polygon
30! grid_spacepercen_within_reg_providing_polys: Subroutine to compute the percentage of grid space of a series of grid
31!   cells which are encompassed by a polygon providing coordinates of the resultant polygons
32! gridpoints_InsidePolygon: Subroutine to determine if a series of grid points are inside a polygon
33!   following ray casting algorithm
34! Heron_area_triangle: Subroutine to compute area of a triangle using Heron's formula
35! intersectfaces: Subroutine to provide if two faces of two polygons intersect
36! intersection_2Dlines: Subroutine to provide the intersection point between two lines on the plane using Cramer's method
37! join_polygon: Subroutine to join two polygons
38! look_clockwise_borders: Subroutine to look clock-wise for a next point within a collection of borders
39!   (limits of a region)
40! multi_index_mat2DI: Subroutine to provide the indices of the different locations of a value inside a 2D integer matrix
41! multi_index_mat3DI: Subroutine to provide the indices of the different locations of a value inside a 3D integer matrix
42! multi_index_mat4DI: Subroutine to provide the indices of the different locations of a value inside a 4D integer matrix
43! multi_index_mat2DRK: Subroutine to provide the indices of the different locations of a value inside a 2D RK matrix
44! multi_index_mat3DRK: Subroutine to provide the indices of the different locations of a value inside a 3D RK matrix
45! multi_index_mat4DRK: Subroutine to provide the indices of the different locations of a value inside a 4D RK matrix
46! multi_spaceweightstats_in1DRKno_slc3v3: Subroutine to compute an spatial statistics value from a 1D RK matrix without
47!   running one into a matrix of 3-variables slices of rank 3 using spatial weights
48! multi_spaceweightstats_in2DRKno_slc3v3: Subroutine to compute an spatial statistics value from a 2D RK matrix without
49!   running one into a matrix of 3-variables slices of rank 3 using spatial weights
50! multi_spaceweightstats_in3DRK3_slc3v3: Subroutine to compute an spatial statistics value from a 3D RK matrix using
51!   3rd dimension as running one into a matrix of 3-variables slices of rank 3 using spatial weights
52! multi_spaceweightstats_in3DRK3_slc3v4: Subroutine to compute an spatial statistics value from a 3D RK matrix using
53!   3rd dimension as running one into a matrix of 3-variables slices of rank 4 using spatial weights
54! NcountR: Subroutine to count real values
55! paths_border: Subroutine to search the paths of a border field.
56! path_properties: Subroutine to determine the properties of a path
57! percentiles_R_K*D: Subroutine to compute the percentiles of a *D R_K array along given set of axis
58! point_in_face: Function to determine if a given point is on a face of a polygon
59! point_inside: Function to determine if a given point is inside a polygon providing its sorted vertices
60! poly_has_point: Function to determine if a polygon has already a given point as one of its vertex
61! polygon_properties: Subroutine to determine the properties of a polygon (as .TRUE. matrix)
62! polygons: Subroutine to search the polygons of a border field. FORTRAN based. 1st = 1!
63! polygons_t: Subroutine to search the polygons of a temporal series of boolean fields. FORTRAN based. 1st = 1!
64! poly_overlap_tracks: Subroutine to determine tracks of a series of consecutive 2D field with polygons using
65!   maximum overlaping/coincidence
66! PrintQuantilesR_K: Subroutine to print the quantiles of values REAL(r_k)
67! poly_overlap_tracks_area: Subroutine to determine tracks of a series of consecutive 2D field with polygons using
68!   maximum overlaping/coincidence filtrered by a minimal area
69! poly_overlap_tracks_area_ascii: Subroutine to determine tracks of a series of consecutive 2D field with polygons using maximum
70!   overlaping/coincidence filtrered by a minimal area writting theoutput on an ASCII file (memory limitations)
71! quantilesR_K: Subroutine to provide the quantiles of a given set of values of type real 'r_k'
72! rand_sample: Subroutine to randomly sample a range of indices
73! read_finaltrack_ascii: Subroutine to read the final trajectories from an ASCII file
74! read_overlap_single_track_ascii: Subroutine to read the values for a given trajectory
75! read_overlap_polys_ascii: Subroutine to read from an ASCII file the associated polygons at a given time-step
76! read_overlap_tracks_ascii: Subroutine to write to an ASCII the polygons associated to a trajectory at a given time step
77! reconstruct_matrix: Subroutine to reconstruct a 2D matrix from a pair of syncronized vectors with the positions on x
78!   and y coordinates
79! runmean_F1D: Subroutine fo computing the running mean of a given set of float 1D values
80! shoelace_area_polygon: Computing the area of a polygon using sholace formula
81! sort_polygon: Subroutine to sort a polygon using its center as average of the coordinates and remove duplicates
82! SortR_K*: Subroutine receives an array x() r_K and sorts it into ascending order.
83! spacepercen: Subroutine to compute the space-percentages of a series of grid cells (B) into another series of grid-cells (A)
84! spaceweightstats: Subroutine to compute an spatial statistics value from a matrix B into a matrix A using weights
85! StatsR_K: Subroutine to provide the minmum, maximum, mean, the quadratic mean, and the standard deviation of a
86!   series of r_k numbers
87! SwapR_K*: Subroutine swaps the values of its two formal arguments.
88! unique_matrixRK2D: Subroutine to provide the unique values within a 2D RK matrix
89! write_finaltrack_ascii: Subroutine to read the final trajectories into an ASCII file
90! write_overlap_polys_ascii: Subroutine to write to an ASCII file the associated polygons at a given time-step
91! write_overlap_tracks_ascii: Subroutine to write to an ASCII the polygons associated to a trajectory at a given time step
92
93!!! *Functions/Subroutines to sort values adpated. The method used is usually referred to as "selection" method.
94! from: http://www.cs.mtu.edu/~shene/COURSES/cs201/NOTES/chap08/sorting.f90
95
96  USE module_definitions
97  USE module_generic
98
99  CONTAINS
100
101  SUBROUTINE fill3DI_2Dvec(matind, inmat, id1, id2, od1, od2, od3, outmat)
102! Subroutine to fill a 3D integer matrix from a series of indices from a 2D matrix
103
104    IMPLICIT NONE
105
106    INTEGER, INTENT(in)                                  :: id1, id2, od1, od2, od3
107    INTEGER, DIMENSION(id1,id2), INTENT(in)              :: inmat
108    INTEGER, DIMENSION(od1,od2), INTENT(in)              :: matind
109    INTEGER, DIMENSION(od1,od2,od3), INTENT(out)         :: outmat
110
111! Local
112    INTEGER                                              :: i, j
113
114!!!!!!! Variables
115! matind: equivalence on the 2D space of the location in inmat
116! inmat: values of the input matrix (1Dvec, time)
117! id1/2: dimensions of the input matrix
118! od1/3: dimensions of the output matrix
119! outmat: output matrix
120! NOTE: id2 == od3
121
122    fname = 'fill3DR_2Dvec'
123
124    DO i=1, od1
125      DO j=1, od2
126        IF (matind(i,j) /= -1) THEN
127          outmat(i,j,:) = inmat(matind(i,j),:)
128        ELSE
129          outmat(i,j,:) = fillvalI
130        END IF
131      END DO
132    END DO
133
134  END SUBROUTINE fill3DI_2Dvec
135
136  SUBROUTINE fill3DR_2Dvec(matind, inmat, id1, id2, od1, od2, od3, outmat)
137! Subroutine to fill a 3D float matrix from a series of indices from a 2D matrix
138
139    IMPLICIT NONE
140
141    INTEGER, INTENT(in)                                  :: id1, id2, od1, od2, od3
142    REAL(r_k), DIMENSION(id1,id2), INTENT(in)            :: inmat
143    INTEGER, DIMENSION(od1,od2), INTENT(in)              :: matind
144    REAL(r_k), DIMENSION(od1,od2,od3), INTENT(out)       :: outmat
145
146! Local
147    INTEGER                                              :: i, j
148
149!!!!!!! Variables
150! matind: equivalence on the 2D space of the location in inmat
151! inmat: values of the input matrix (1Dvec, time)
152! id1/2: dimensions of the input matrix
153! od1/3: dimensions of the output matrix
154! outmat: output matrix
155! NOTE: id2 == od3
156
157    fname = 'fill3DR_2Dvec'
158
159    DO i=1, od1
160      DO j=1, od2
161        IF (matind(i,j) /= -1) THEN
162          outmat(i,j,:) = inmat(matind(i,j),:)
163        ELSE
164          outmat(i,j,:) = fillval64
165        END IF
166      END DO
167    END DO
168
169  END SUBROUTINE fill3DR_2Dvec
170
171  SUBROUTINE reconstruct_matrix(vectorXpos, vectorYpos, dvec, Xmin, Xmax, Ymin, Ymax, dmatx, dmaty,   &
172    matProj, maxdiff, matind, matX, matY, matdiff)
173! Subroutine to reconstruct a 2D matrix from a pair of syncronized vectors with the positions on x
174!   and y coordinates
175
176    IMPLICIT NONE
177
178    INTEGER, INTENT(in)                                  :: dvec, dmatx, dmaty
179    REAL(r_k), DIMENSION(dvec), INTENT(in)               :: vectorXpos, vectorYpos
180    REAL(r_k), INTENT(in)                                :: Xmin, Xmax, Ymin, Ymax, maxdiff
181    CHARACTER(len=50), INTENT(in)                        :: matPRoj
182    INTEGER, DIMENSION(dmatx, dmaty), INTENT(out)        :: matind
183    REAL(r_k), DIMENSION(dmatx, dmaty), INTENT(out)      :: matX, matY, matdiff
184
185! Local
186    INTEGER                                              :: i,j,iv, idiff, jdiff
187    REAL(r_k)                                            :: ddx, ddy, Xpos, Ypos, mindiff
188    REAL(r_k), DIMENSION(dmatx,dmaty)                    :: diff
189    REAL(r_k)                                            :: nXpos, xXpos, nYpos, xYpos
190    INTEGER, DIMENSION(2)                                :: mindiffloc
191    CHARACTER(LEN=50)                                    :: RSa, RSb
192
193!!!!!!! Variables
194! vectorXpos, vectorYpos: syncronized vectors with the x,y coordinates from which the matrix will be reconstructed
195! dvec: quantitiy of coordinates to use
196! Xmin,Xmax,Ymin,Ymax: Location range of the matrix to be reconstructed
197! maxdiff: Authorized maximum distance between matrix location and vector location
198! dmatx, dmaty: Size in grid points of the matrix to be reconstructed
199! matProj: Assumed projection of the values of the matrix
200!   'latlon': regular lat/lon projection
201! matind: matrix with the correspondant indiced from the vector of positions
202! matX, matY: matrix with the coordinates of the elements of the matrix
203! matdiff: matrix with the differences at each grid point
204
205    fname = 'reconstruct_matrix'
206
207    matind = -oneRK
208    matdiff = -oneRK
209
210    nXpos = MINVAL(vectorXpos)
211    xXpos = MAXVAL(vectorXpos)
212    nYpos = MINVAL(vectorYpos)
213    xYpos = MAXVAL(vectorYpos)
214    PRINT *, 'Limits of the positions to localize in a matrix: longitudes:', nXpos,  &
215     ' ,',xXpos, ' latitudes:', nYpos, ' ,', xYpos
216
217    Projection: SELECT CASE(TRIM(matProj))
218
219    CASE('latlon')
220      ! Resolution along matrix axes
221      ddx = (Xmax - Xmin)/(dmatx-1)
222      ddy = (Ymax - Ymin)/(dmaty-1)
223
224      ! Filling matrix positions
225      DO i=1,dmatx
226        Xpos = Xmin + ddx*(i-1)
227        DO j=1,dmaty
228          Ypos = Ymin + ddy*(j-1)
229          matX(i,j) = Xpos
230          matY(i,j) = Ypos
231        END DO
232      END DO
233
234    CASE DEFAULT
235      msg = "Projection of matrix '" // TRIM(matProj) // "' not ready " // CHAR(10) //                &
236        "  Available ones: 'latlon'"
237      CALL ErrMsg(msg, fname, -1)
238    END SELECT Projection
239
240    ! Let's do it properly...
241    DO iv=1,dvec
242      diff = SQRT((matX - vectorXpos(iv))**2 + (matY - vectorYpos(iv))**2)
243      mindiffloc = MINLOC(diff)
244      mindiff = MINVAL(diff)
245      IF (mindiff > maxdiff) THEN
246        PRINT *,'  vectorXpos:', vectorXpos(iv), 'vectorYpos:', vectorYpos(iv)
247        !PRINT *,'  Xpos:', Xpos, 'Ypos:', Ypos
248        WRITE(RSa, '(f20.10)')mindiff
249        WRITE(RSb, '(f20.10)')maxdiff
250        msg = 'Difference: ' // TRIM(RSa) // ' overpasses the maximum authorized distance: ' //   &
251          TRIM(RSb)
252        CALL ErrMsg(msg, fname, -1)
253      ELSE
254        i = mindiffloc(1)
255        j = mindiffloc(2)
256        matind(i,j) = iv
257        matdiff(i,j) = mindiff
258      END IF
259    END DO
260
261    RETURN
262
263  END SUBROUTINE reconstruct_matrix
264
265  SUBROUTINE read_finaltrack_ascii(funit, dt, itrack, ftrack)
266! Subroutine to read the final trajectories from an ASCII file
267
268    IMPLICIT NONE
269
270    INTEGER, INTENT(in)                                  :: funit, dt, itrack
271    REAL(r_k), DIMENSION(5,dt), INTENT(out)              :: ftrack
272
273! Local
274    INTEGER                                              :: i, j, it
275    LOGICAL                                              :: found
276
277!!!!!!! Variables
278! funit: unit where to write the trajectory
279! dt: number of time-steps
280! itrack: trajectory to read the values
281! ftrack: values of the trajectory
282
283    fname = 'read_finaltrack_ascii'
284
285    ftrack = 0.
286   
287    REWIND(funit)
288
289    it = 1
290    DO WHILE (.NOT.found)
291
292      READ(funit,10)ftrack(1,1), Str1, ((ftrack(i,j),Str1,i=2,5),Str1,j=1,dt)
293      IF (INT(ftrack(1,1)) == itrack) THEN
294        ftrack(1,2:dt) = ftrack(1,1)
295        found = .TRUE.
296      END IF
297
298      ! Just in case
299      IF (it >= dt) found = .TRUE.
300
301    END DO
302
303    RETURN
304
305 10 FORMAT(I10000000,1x,A1,1x,10000000(4(F20.10,A1),A1))
306
307  END SUBROUTINE read_finaltrack_ascii
308
309  SUBROUTINE write_finaltrack_ascii(funit, dt, ftrack)
310! Subroutine to write the final trajectories into an ASCII file
311
312    IMPLICIT NONE
313
314    INTEGER, INTENT(in)                                  :: funit, dt
315    REAL(r_k), DIMENSION(5,dt), INTENT(in)               :: ftrack
316
317! Local
318    INTEGER                                              :: i, j
319
320!!!!!!! Variables
321! funit: unit where to write the trajectory
322! dt: number of time-steps
323! ftrack: values of the trajectory
324
325    fname = 'write_finaltrack_ascii'
326    WRITE(funit,10)INT(ftrack(1,1)), ';', ((ftrack(i,j), ',', i=2,5), ':', j=1,dt)
327
328    RETURN
329
330 10 FORMAT(I10,1x,A1,1x,10000000(4(F20.10,A1),A1))
331
332  END SUBROUTINE write_finaltrack_ascii
333
334  SUBROUTINE read_overlap_single_track_ascii(funit, dt, Nxp, Nxtr, itrack, strack)
335! Subroutine to read the values for a given trajectory
336
337    IMPLICIT NONE
338
339    INTEGER, INTENT(in)                                  :: funit, dt, Nxp, Nxtr, itrack
340    REAL(r_k), DIMENSION(5,Nxp,dt), INTENT(out)          :: strack
341
342! Local
343    INTEGER                                              :: i,j,k,l
344    INTEGER                                              :: read_it, itt, it, Ntrcks
345    INTEGER, DIMENSION(Nxp)                              :: Npindep
346    LOGICAL                                              :: looking
347    REAL(r_k), DIMENSION(5,Nxp,Nxtr)                     :: trcks
348
349!!!!!!! Variables
350! funit: unit from where retrieve the values of the trajectory
351! dt: time-dimension
352! Nxp: maximum allowed number of polygons per time-step
353! Nxp: maximum allowed number of trajectories
354! itrack: trajectory Id to look for
355! strack: Values for the given trajectory
356
357    fname = 'read_overlap_single_track_ascii'
358
359    strack = 0.
360
361    REWIND(funit)
362
363    looking = .TRUE.
364    itt = 0
365    it = 1
366    DO WHILE (looking)
367      READ(funit,5,END=100)Str10, read_it
368
369      READ(funit,*)Ntrcks
370      DO i=1, Ntrcks
371        READ(funit,10)l, Str1, Npindep(i), Str1, ((trcks(k,j,i),Str1,k=1,5),Str1,j=1,Npindep(i))
372      END DO
373
374      ! There is the desired trajectory at this time-step?
375      IF (ANY(INT(trcks(1,1,:)) == itrack)) THEN
376        itt = itt + 1
377        DO i=1, Ntrcks
378          IF (INT(trcks(1,1,i)) == itrack) THEN
379            DO j=1, Npindep(i)
380              strack(:,j,it) = trcks(:,j,i)
381            END DO
382          END IF
383        END DO
384      ELSE
385        ! It trajectory has already been initialized this is the end
386        IF (itt > 0) looking = .FALSE.
387      END IF
388
389      ! Just in case... ;)
390      IF (read_it >= dt) looking = .FALSE.
391      it = it + 1
392
393      IF (it > dt) looking = .FALSE.
394
395    END DO
396
397 100 CONTINUE
398
399    RETURN
400
401  5 FORMAT(A10,1x,I4)
402 10 FORMAT(I4,1x,A1,I4,1x,A1,1x,1000000(5(F20.10,A1),A1))
403
404  END SUBROUTINE read_overlap_single_track_ascii
405
406  SUBROUTINE read_overlap_tracks_ascii(funit, tstep, Nxp, Ntrcks, trcks)
407! Subroutine to write to an ASCII the polygons associated to a trajectory at a given time step
408
409    IMPLICIT NONE
410
411    INTEGER, INTENT(in)                                  :: funit, tstep, Nxp
412    INTEGER, INTENT(out)                                 :: Ntrcks
413    REAL(r_k), DIMENSION(5,Nxp,Nxp), INTENT(out)         :: trcks
414
415! Local
416    INTEGER                                              :: i, j, k, l, Npindep
417    INTEGER                                              :: read_it
418
419!!!!!!! Variables
420! funit: unit where to write the file
421! tstep: time-step to write the trajectories
422! Nxp: maximum number of polygons per time-step
423! Nrtcks: Number of trajectories of the given time-step
424! trcks: trajectories
425
426    fname = 'read_overlap_tracks_ascii'
427
428    Ntrcks = 0
429    trcks = 0
430
431    READ(funit,5)Str10, read_it
432
433    IF (read_it /= tstep) THEN
434      WRITE(numSa,'(I4)')read_it
435      WRITE(numSb,'(I4)')tstep
436      msg = 'File time-step;' // TRIM(numSa) // ' does not coincide with the one from program:' //    &
437        TRIM(numSb)
438    END IF
439
440    READ(funit,*)Ntrcks
441    DO i=1, Ntrcks
442      READ(funit,10)l, Str1, Npindep, Str1, ((trcks(k,j,i),Str1,k=1,5),Str1,j=1,Npindep)
443    END DO
444
445    RETURN
446
447  5 FORMAT(A10,1x,I4)
448 10 FORMAT(I4,1x,A1,I4,1x,A1,1x,1000000(5(F20.10,A1),A1))
449
450  END SUBROUTINE read_overlap_tracks_ascii
451
452  SUBROUTINE write_overlap_tracks_ascii(funit, tstep, Nxp, Ntrcks, trcks)
453! Subroutine to write to an ASCII the polygons associated to a trajectory at a given time step
454
455    IMPLICIT NONE
456
457    INTEGER, INTENT(in)                                  :: funit, tstep, Nxp, Ntrcks
458    REAL(r_k), DIMENSION(5,Nxp,Ntrcks)                   :: trcks
459
460! Local
461    INTEGER                                              :: i, j, k, ii, Npindep, Nrealtracks
462
463!!!!!!! Variables
464! funit: unit where to write the file
465! tstep: time-step to write the trajectories
466! Nxp: maximum number of polygons per time-step
467! Nrtcks: Number of trajectories of the given time-step
468! trcks: trajectories
469
470    fname = 'write_overlap_tracks_ascii'
471
472    WRITE(funit,5)'time-step:', tstep
473
474    ! Looking for the non-zero trajectories
475    Nrealtracks = 0
476    DO i=1, Ntrcks
477      Npindep = COUNT(trcks(2,:,i) /= zeroRK)
478      IF (Npindep /= 0) Nrealtracks = Nrealtracks + 1
479    END DO
480    WRITE(funit,*)Nrealtracks
481
482    ! Only writting the trajectories with values
483    ii = 1
484    DO i=1, Ntrcks
485      Npindep = COUNT(trcks(2,:,i) /= zeroRK)
486      IF (Npindep /= 0) THEN
487        WRITE(funit,10)ii,';', Npindep, ';', ((trcks(k,j,i),',',k=1,5),':',j=1,Npindep)
488        ii = ii + 1
489      END IF
490    END DO
491
492    RETURN
493
494  5 FORMAT(A10,1x,I4)
495 10 FORMAT(I4,1x,A1,I4,1x,A1,1x,1000000(5(F20.10,A1),A1))
496
497  END SUBROUTINE write_overlap_tracks_ascii
498
499  SUBROUTINE read_overlap_polys_ascii(funit, tstep, Nxp, Nindep, SpIndep, NpIndep, pIndep)
500! Subroutine to read from an ASCII file the associated polygons at a given time-step
501
502    IMPLICIT NONE
503
504    INTEGER, INTENT(in)                                  :: funit, tstep, Nxp
505    INTEGER, INTENT(out)                                 :: Nindep
506    INTEGER, DIMENSION(Nxp), INTENT(out)                 :: SpIndep, NpIndep
507    INTEGER, DIMENSION(Nxp,Nxp), INTENT(out)             :: pIndep
508
509! Local
510    INTEGER                                              :: i, j, k
511    INTEGER                                              :: read_it
512
513!!!!!!! Variables
514! funit: unit associated to the file
515! tstep: time-step of the values
516! Nxp: allowed maximum numbe of polygons per time-step
517! Nindpe: Number of independent polygons at this time-step
518! SpIndep: Associated polygon to the independent one from the previous time-step
519! NpIndep: Number of associated polygons to the independent time-step
520! pIndep: polygons associated to a given independent polygon
521
522    fname = 'read_overlap_polys_ascii'
523
524    Nindep = 0
525    SpIndep = 0
526    NpIndep = 0
527
528    READ(funit,5)Str10, read_it
529
530    IF (read_it /= tstep) THEN
531      WRITE(numSa,'(I4)')read_it
532      WRITE(numSb,'(I4)')tstep
533      msg = 'File time-step;' // TRIM(numSa) // ' does not coincide with the one from program:' //    &
534        TRIM(numSb)
535    END IF
536
537    READ(funit,*)Nindep
538    DO i=1, Nindep
539      READ(funit,10) k, Str1, SpIndep(i), Str1, NpIndep(i), Str1, (pIndep(i,j), Str1, j=1,NpIndep(i))
540    END DO
541
542    RETURN
543
544  5 FORMAT(A10,1x,I4)
545 10 FORMAT(I4,1x,A1,1x,I4,1x,A1,1x,I4,A1,1x,100000(I4,A1))
546
547  END SUBROUTINE read_overlap_polys_ascii
548
549  SUBROUTINE write_overlap_polys_ascii(funit, tstep, Nxp, Nindep, SpIndep, NpIndep, pIndep)
550! Subroutine to write into an ASCII file the associated polygons at a given time-step
551
552    IMPLICIT NONE
553
554    INTEGER, INTENT(in)                                  :: funit, tstep, Nxp, Nindep
555    INTEGER, DIMENSION(Nindep), INTENT(in)               :: SpIndep, NpIndep
556    INTEGER, DIMENSION(Nindep,Nxp), INTENT(in)           :: pIndep
557
558! Local
559    INTEGER                                              :: i, j
560
561!!!!!!! Variables
562! funit: unit associated to the file
563! tstep: time-step of the values
564! Nxp: allowed maximum numbe of polygons per time-step
565! Nindpe: Number of independent polygons at this time-step
566! SpIndep: Associated polygon to the independent one from the previous time-step
567! NpIndep: Number of associated polygons to the independent time-step
568! pIndep: polygons associated to a given independent polygon
569
570    fname = 'write_overlap_polys_ascii'
571
572    WRITE(funit,5)'time-step:', tstep
573    WRITE(funit,*)Nindep, ' ! Number of independent polygons'
574    DO i=1, Nindep
575      WRITE(funit,10) i, ';', SpIndep(i), ';', NpIndep(i), ':', (pIndep(i,j), ',', j=1,NpIndep(i))
576    END DO
577
578    RETURN
579
580  5 FORMAT(A10,1x,I4)
581 10 FORMAT(I4,1x,A1,1x,I4,1x,A1,1x,I4,A1,1x,100000(I4,A1))
582
583  END SUBROUTINE write_overlap_polys_ascii
584
585  SUBROUTINE poly_overlap_tracks_area_ascii(dbg, compute, dx, dy, dt, minarea, inNallpolys, allpolys, &
586    ctrpolys, areapolys, Nmaxpoly, Nmaxtracks, methodmulti)
587! Subroutine to determine tracks of a series of consecutive 2D field with polygons using maximum
588!   overlaping/coincidence filtrered by a minimal area writting theoutput on an ASCII file (memory limitations)
589
590    IMPLICIT NONE
591
592    LOGICAL, INTENT(in)                                  :: dbg
593    CHARACTER(LEN=*), INTENT(in)                         :: compute, methodmulti
594    INTEGER, INTENT(in)                                  :: dx, dy, dt, Nmaxpoly, Nmaxtracks
595    INTEGER, DIMENSION(dt), INTENT(in)                   :: inNallpolys
596    INTEGER, DIMENSION(dx,dy,dt), INTENT(in)             :: allpolys
597    REAL(r_k), INTENT(in)                                :: minarea
598    REAL(r_k), DIMENSION(2,Nmaxpoly,dt), INTENT(in)      :: ctrpolys
599    REAL(r_k), DIMENSION(Nmaxpoly,dt), INTENT(in)        :: areapolys
600
601! Local
602    INTEGER                                              :: i, j, ip, it, iip, itt, iit
603    INTEGER                                              :: fprevunit, ftrackunit, ftrunit, ierr, ios
604    LOGICAL                                              :: file_exist, dooverlap, dotracks, doftracks
605    REAL(r_k), DIMENSION(Nmaxpoly)                       :: Aprevpolys, Acurrpolys
606    REAL(r_k), DIMENSION(2,Nmaxpoly)                     :: Cprevpolys, Ccurrpolys
607    INTEGER, DIMENSION(dx,dy)                            :: meetpolys, searchpolys
608    INTEGER, DIMENSION(Nmaxpoly)                         :: coincidencies
609    INTEGER, DIMENSION(Nmaxpoly)                         :: prevID, currID
610    REAL(r_k), DIMENSION(5,Nmaxpoly,Nmaxtracks,2)        :: tracks
611    REAL(r_k), DIMENSION(5,dt)                           :: finaltracks
612    INTEGER, DIMENSION(:), ALLOCATABLE                   :: coins
613    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: coinsNpts
614    INTEGER                                              :: Nmeet, Nsearch, Nindep
615    INTEGER, DIMENSION(2)                                :: Nindeppolys, Npolystime
616    CHARACTER(len=5)                                     :: NcoinS
617    INTEGER, DIMENSION(Nmaxpoly,Nmaxpoly,2)              :: polysIndep
618    INTEGER, DIMENSION(Nmaxpoly,2)                       :: NpolysIndep
619    INTEGER, DIMENSION(Nmaxpoly,2)                       :: SpolysIndep
620    INTEGER                                              :: iindep, iiprev
621    INTEGER                                              :: Nprev, NNprev, Ntprev
622    LOGICAL                                              :: Indeppolychained
623    INTEGER                                              :: itrack, ictrack
624    INTEGER                                              :: ixp, iyp, ttrack
625    INTEGER, DIMENSION(2)                                :: Ntracks
626    INTEGER                                              :: idtrack, maxtrack
627    REAL(r_k), DIMENSION(5,Nmaxpoly,dt)                  :: singletrack
628    REAL(r_k)                                            :: totArea, dist, mindist, maxarea, areai
629
630!!!!!!! Variables
631! dx,dy,dt: space/time dimensions
632! compute: how to copmute
633!   'scratch': everything from the beginning
634!   'continue': skipt that parts which already have the ascii file written
635! inNallpolys: Vector with the original number of polygons at each time-step
636! allpolys: Series of 2D field with the polygons
637! minarea: minimal area (in same units as areapolys) to perform the tracking
638! ctrpolys: center of the polygons
639! areapolys: area of the polygons
640! Nmaxpoly: Maximum possible number of polygons
641! Nmaxtracks: maximum number of tracks
642! methodmulti: methodology to follow when multiple polygons are given for the same track
643!   'mean': get coordinates from the areal-weighted mean of the centers of the given polygons and their areas
644!   'largest': get the coorindates of the largest polygon
645!   'closest': get the coordinates of the closest polygon
646
647    fname = 'poly_overlap_tracks_area_ascii'
648
649    IF (dbg) PRINT *,TRIM(fname)
650
651    SELECT CASE (TRIM(compute))
652      CASE ('scratch')
653        dooverlap = .TRUE.
654        dotracks = .TRUE.
655        doftracks = .TRUE.
656      CASE ('continue')
657        INQUIRE(file='polygons_overlap.dat', exist=file_exist)
658        IF (.NOT.file_exist) THEN
659          dooverlap = .TRUE.
660        ELSE
661          IF (dbg) THEN
662            PRINT *, TRIM(warnmsg)
663            PRINT *,"  "//TRIM(fname) // ": File 'polygons_overlap.dat' already exists, skipping it !!"
664          END IF
665          dooverlap = .FALSE.
666        END IF
667        INQUIRE(file='trajectories_overlap.dat', exist=file_exist)
668        IF (.NOT.file_exist) THEN
669          dotracks = .TRUE.
670        ELSE
671          IF (dbg) THEN
672            PRINT *, TRIM(warnmsg)
673            PRINT *, "  " // TRIM(fname) // ": File 'trajectories_overlap.dat' already exists, " //   &
674              "skipping it !!"
675          END IF
676          dotracks = .FALSE.
677        END IF
678        INQUIRE(file='trajectories.dat', exist=file_exist)
679        IF (.NOT.file_exist) THEN
680          doftracks = .TRUE.
681        ELSE
682          IF (dbg) THEN
683            PRINT *, TRIM(warnmsg)
684            PRINT *,"  "//TRIM(fname) // ": File 'trajectories.dat' already exists, skipping it !!"
685          END IF
686          doftracks = .FALSE.
687        END IF
688    CASE DEFAULT
689      msg = "compute case: '" // TRIM(compute) // "' not ready !!"
690      CALL ErrMsg(msg, fname, -1)
691    END SELECT
692
693    ! Checking multi-polygon methodology
694    IF ( (TRIM(methodmulti) /= 'mean') .AND. (TRIM(methodmulti) /= 'largest') .AND.                   &
695      (TRIM(methodmulti) /= 'closest')) THEN
696      msg= "methodology for multiple-polygons: '"//TRIM(methodmulti)//"' not ready" // NEW_LINE('a')//&
697        " available ones: 'mean', 'largest', 'closest'"
698      CALL ErrMsg(msg, fname, -1)
699    END IF
700
701    IF (dooverlap) THEN
702      ! ASCII file for all the polygons and their previous associated one
703      fprevunit = freeunit()
704      OPEN(fprevunit, file='polygons_overlap.dat', status='new', form='formatted', iostat=ios)
705      msg = "Problems opening file: 'polygons_overlap.dat'"
706      IF (ios == 17) PRINT *,"  Careful: 'polygons_overlap.dat' already exists!!"
707      CALL ErrMsg(msg, fname, ios)
708
709      ! Number of independent polygons by time step
710      Nindeppolys = 0
711      ! Number of polygons attached to each independent polygons by time step
712      NpolysIndep = 0
713      ! ID of searching polygon attached to each independent polygons by time step
714      SpolysIndep = 0
715      ! ID of polygons attached to each independent polygons by time step
716      polysIndep = 0
717      ! ID of polygons from previous time-step
718      prevID = 0
719      ! ID of polygons from current time-step
720      currID = 0
721
722      ! First time-step all are independent polygons
723      it = 1
724      Nmeet = inNallpolys(it)
725      Nindeppolys(it) = Nmeet
726      ip = 0
727      meetpolys = allpolys(:,:,it)
728      DO i=1, Nmeet
729        IF (areapolys(i,it) >= minarea) THEN
730          ip = ip + 1
731          SpolysIndep(ip,it) = i
732          currID(ip) = i
733          Acurrpolys(ip) = areapolys(i,it)
734          Ccurrpolys(1,ip) = ctrpolys(1,i,it)
735          Ccurrpolys(2,ip) = ctrpolys(2,i,it)
736          NpolysIndep(ip,it) = 1
737          polysIndep(ip,1,it) = i
738        ELSE
739          WHERE (meetpolys == i)
740            meetpolys = 0
741          END WHERE
742        END IF
743      END DO
744      Nindeppolys(1) = ip
745      Npolystime(1) = ip
746 
747      ! Starting step
748      it = 0
749      IF (dbg) THEN
750        PRINT *,'  time step:',it+1,' number to look polygons:', Nmeet,' searching polygons:',0
751        PRINT *,'    number of independent polygons:', Nindeppolys(it+1)
752        PRINT *,'    indep_polygon prev_step_polygon Nassociated_polygons curr_ass_polygons _______'
753        DO i=1, Nindeppolys(it+1)
754          PRINT *,i, SpolysIndep(i,it+1), NpolysIndep(i,it+1), ':',                                     &
755            polysIndep(i,1:NpolysIndep(i,it+1),it+1)
756        END DO
757      END IF
758      ! Writting to the ASCII file Independent polygons and their associated
759      CALL write_overlap_polys_ascii(fprevunit,it+1, Nmaxpoly, Nindeppolys(it+1),                       &
760        SpolysIndep(1:Nindeppolys(it+1),it+1), NpolysIndep(1:Nindeppolys(it+1),it+1),                   &
761        polysIndep(1:Nindeppolys(it+1),:,it+1))
762
763      it = 1
764      ! Looking for the coincidencies at each time step
765      DO iit=1, dt-1
766        ! Number of times that a polygon has a coincidence
767        coincidencies = 0
768 
769        ! Preparing for next time-step
770        searchpolys = meetpolys
771        prevID = 0
772        prevID = currID
773        Aprevpolys = Acurrpolys
774        Cprevpolys = Ccurrpolys
775
776        Nmeet = inNallpolys(iit+1)
777        meetpolys = allpolys(:,:,iit+1)
778        ip = 0
779        DO i=1, Nmeet
780          IF (areapolys(i,iit+1) >= minarea) THEN
781            ip = ip + 1
782            currID(ip) = i
783            Acurrpolys(ip) = areapolys(i,iit+1)
784            Acurrpolys(ip) = areapolys(i,iit+1)
785            Ccurrpolys(1,ip) = ctrpolys(1,i,iit+1)
786            Ccurrpolys(2,ip) = ctrpolys(2,i,iit+1)
787          ELSE
788            WHERE (meetpolys == i)
789              meetpolys = 0
790            END WHERE
791          END IF
792        END DO
793        Nindeppolys(it+1) = ip
794        Npolystime(it+1) = ip
795
796        ! Looking throughout the independent polygons
797        Nmeet = Nindeppolys(it+1)
798        !Nsearch = Nindeppolys(it)
799        ! Previous space might have more polygons that their number of independent ones
800        Nsearch = Npolystime(it)
801
802        IF (ALLOCATED(coins)) DEALLOCATE(coins)
803        ALLOCATE(coins(Nmeet), STAT=ierr)
804        msg="Problems allocating 'coins'"
805        CALL ErrMsg(msg,fname,ierr)
806
807        IF (ALLOCATED(coinsNpts)) DEALLOCATE(coinsNpts)
808        ALLOCATE(coinsNpts(Nmeet, Nsearch), STAT=ierr)
809        msg="Problems allocating 'coinsNpts'"
810        CALL ErrMsg(msg,fname,ierr)
811
812        CALL coincidence_all_polys_area(dbg, dx, dy, Nmeet, currID, meetpolys, Ccurrpolys(:,1:Nmeet),   &
813          Nsearch, prevID, searchpolys, Cprevpolys(:,1:Nsearch), Aprevpolys(1:Nsearch), coins,          &
814          coinsNpts)
815
816        ! Counting the number of times that a polygon has a coincidency
817        IF (dbg) THEN
818          PRINT *,'  Coincidencies for the given time-step:', iit+1,' _______'
819          DO i=1, Nmeet
820            PRINT *,currID(i), coins(i),' N search pts:', coinsNpts(i,:)
821          END DO
822        END IF
823
824        ! Looking for the same equivalencies
825        Nindep = 0
826        DO i=1, Nmeet
827          IF (coins(i) == -1) THEN
828            Nindep = Nindep + 1
829            SpolysIndep(Nindep,it+1) = -1
830            NpolysIndep(Nindep,it+1) = NpolysIndep(Nindep,it+1) + 1
831            polysIndep(Nindep,NpolysIndep(Nindep,it+1),it+1) = currID(i)
832          ELSE IF (coins(i) == -9) THEN
833            WRITE(NcoinS,'(I5)')coins(i)
834            msg="coins= "//TRIM(NcoinS)//" This is an error. One should have always only one " //      &
835              "coincidence of polygon"
836            CALL ErrMsg(msg, fname, -1)
837          ELSE
838            ! Looking for coincidences with previous independent polygons
839            DO ip=1, Nsearch
840              ! Looking into the polygons associated
841              NNprev = NpolysIndep(ip,it)
842              DO j=1, NNprev
843                IF (coins(i) == polysIndep(ip,j,it)) THEN
844                  ! Which index corresponds to this coincidence?
845                  iindep = Index1DArrayI(SpolysIndep(1:Nindep,it+1), Nindep, coins(i))
846                  IF (iindep == -1) THEN
847                    Nindep = Nindep + 1
848                    SpolysIndep(Nindep,it+1) = coins(i)
849                  END IF
850                  iindep = Index1DArrayI(SpolysIndep(1:Nindep,it+1), Nindep, coins(i))
851                  IF (iindep < 0) THEN
852                    PRINT *,'    Looking for:', coins(i)
853                    PRINT *,'    Within:', SpolysIndep(1:Nindep,it+1)
854                    PRINT *,'    Might content:', polysIndep(ip,1:NNprev,it)
855                    PRINT *,'    From an initial list:', coins(1:Nmeet)
856                    msg = 'Wrong index! There must be an index here'
857                    CALL ErrMsg(msg,fname,iindep)
858                  END IF
859                  coincidencies(ip) = coincidencies(ip) + 1
860                  NpolysIndep(iindep,it+1) = NpolysIndep(iindep,it+1) + 1
861                  polysIndep(iindep,NpolysIndep(iindep,it+1),it+1) = currID(i)
862                  EXIT
863                END IF
864              END DO
865            END DO
866          END IF
867        END DO
868        Nindeppolys(it+1) = Nindep
869
870        IF (dbg) THEN
871          PRINT *,'  time step:',iit+1,' number to look polygons:', Nmeet,' searching polygons:',Nsearch
872          PRINT *,'    number of independent polygons:', Nindeppolys(it+1)
873          PRINT *,'    indep_polygon prev_step_polygon Nassociated_polygons curr_ass_polygons _______'
874          DO i=1, Nindeppolys(it+1)
875            PRINT *,i, SpolysIndep(i,it+1), NpolysIndep(i,it+1), ':',                                   &
876              polysIndep(i,1:NpolysIndep(i,it+1),it+1)
877          END DO
878        END IF
879
880        ! Writting to the ASCII file Independent polygons and their associated
881        CALL write_overlap_polys_ascii(fprevunit, iit+1, Nmaxpoly, Nindeppolys(it+1),                   &
882          SpolysIndep(1:Nindeppolys(it+1),it+1), NpolysIndep(1:Nindeppolys(it+1),it+1),                 &
883          polysIndep(1:Nindeppolys(it+1),:,it+1))
884        ! Preparing for the next time-step
885        SpolysIndep(:,it) = 0
886        NpolysIndep(:,it) = 0
887        polysIndep(:,:,it) = 0
888        Nindeppolys(it) = Nindeppolys(it+1)
889        SpolysIndep(1:Nindeppolys(it),it) = SpolysIndep(1:Nindeppolys(it+1),it+1)
890        NpolysIndep(1:Nindeppolys(it),it) = NpolysIndep(1:Nindeppolys(it+1),it+1)
891        Npolystime(it) = Npolystime(it+1)
892
893        DO ip=1, Nindeppolys(it)
894          polysIndep(ip,1,it) = polysIndep(ip,1,it+1)
895          polysIndep(ip,2,it) = polysIndep(ip,2,it+1)
896        END DO
897        SpolysIndep(:,it+1) = 0
898        NpolysIndep(:,it+1) = 0
899        polysIndep(:,:,it+1) = 0
900
901      END DO
902      CLOSE(fprevunit)
903      IF (dbg) PRINT *,"  Succesful writting of ASCII chain of polygons 'polygons_overlap.dat' !!"
904    END IF
905    ! ASCII file for all the polygons and their previous associated one
906    fprevunit = freeunit()
907    OPEN(fprevunit, file='polygons_overlap.dat', status='old', form='formatted', iostat=ios)
908    msg = "Problems opening file: 'polygons_overlap.dat'"
909    CALL ErrMsg(msg, fname, ios)
910
911    it = 1
912    IF (dbg) THEN
913      PRINT *,  'Coincidencies to connect _______'
914      DO iit=1, dt
915        ! Reading from the ASCII file Independent polygons and their associated
916        CALL read_overlap_polys_ascii(fprevunit, iit, Nmaxpoly, Nindeppolys(it), SpolysIndep(:,it),   &
917          NpolysIndep(:,it), polysIndep(:,:,it))
918        PRINT *,'  it:', iit, ' Nindep:', Nindeppolys(it)
919        PRINT '(4x,3(A6,1x))','Nindep', 'PrevID', 'IDs'
920        DO ip=1, Nindeppolys(it)
921          PRINT '(4x,I6,A1,I6,A1,100(I6))', ip, ',', SpolysIndep(ip,it), ':',                         &
922            polysIndep(ip,1:NpolysIndep(ip,it),it)
923        END DO
924      END DO
925    END IF
926
927    REWIND(fprevunit)
928
929    ! Trajectories
930    ! It should be done following the number of 'independent' polygons
931    ! One would concatenate that independent polygons which share IDs from one step to another
932    IF (dotracks) THEN
933
934      ! ASCII file for the trajectories
935      ftrackunit = freeunit()
936      OPEN(ftrackunit, file='trajectories_overlap.dat', status='new', form='formatted', iostat=ios)
937      msg = "Problems opening file: 'trajectories_overlap.dat'"
938      IF (ios == 17) PRINT *,"  Careful: 'trajectories_overlap.dat' already exists!!"
939      CALL ErrMsg(msg,fname,ios)
940
941      ! First time-step. Take all polygons
942      itrack = 0
943      tracks = zeroRK
944      Ntracks = 0
945      it = 1
946      iit = 1
947      CALL read_overlap_polys_ascii(fprevunit, iit, Nmaxpoly, Nindeppolys(it), SpolysIndep(:,it),       &
948        NpolysIndep(:,it), polysIndep(:,:,it))
949
950      DO ip=1, Nindeppolys(1)
951        itrack = itrack + 1
952        tracks(1,1,itrack,1) = itrack*1.
953        tracks(2,1,itrack,1) = SpolysIndep(ip,1)
954        tracks(3,1,itrack,1) = ctrpolys(1,ip,1)
955        tracks(4,1,itrack,1) = ctrpolys(2,ip,1)
956        tracks(5,1,itrack,1) = 1
957        Ntracks(1) = Ntracks(1) + 1
958      END DO
959
960      ! Writting first time-step trajectories to the intermediate file
961      CALL write_overlap_tracks_ascii(ftrackunit,iit,Nmaxpoly, Ntracks(it), tracks(:,:,1:Ntracks(it),it))
962
963      ! Looping allover already assigned tracks
964      it = 2
965      maxtrack = Ntracks(1)
966      timesteps: DO iit=2, dt
967        CALL read_overlap_polys_ascii(fprevunit, iit, Nmaxpoly, Nindeppolys(it), SpolysIndep(:,it),     &
968          NpolysIndep(:,it), polysIndep(:,:,it))
969        IF (dbg) PRINT *,'track-timestep:', iit, 'N indep polys:', Nindeppolys(it)
970        ! Indep polygons current time-step
971        current_poly: DO i=1, Nindeppolys(it)
972          IF (dbg) PRINT *,'  curent poly:', i, 'Prev poly:', SpolysIndep(i,it), ' N ass. polygons:',   &
973            NpolysIndep(i,it), 'ass. poly:', polysIndep(i,1:NpolysIndep(i,it),it)
974          Indeppolychained = .FALSE.
975
976          ! Number of tracks previous time-step
977          ! Looping overall
978          it1_tracks: DO itt=1, Ntracks(it-1)
979            itrack = tracks(1,1,itt,it-1)
980            ! Number polygons ID assigned
981            Ntprev = COUNT(tracks(2,:,itt,it-1) /= 0)
982            IF (dbg) PRINT *,itt,'  track:', itrack, 'assigned:', tracks(2,1:Ntprev,itt,it-1)
983
984            ! Looking for coincidencies
985            DO iip=1, Ntprev
986              IF (tracks(2,iip,itt,it-1) == SpolysIndep(i,it)) THEN
987                Indeppolychained = .TRUE.
988                IF (dbg) PRINT *,'    coincidence found by polygon:', tracks(2,iip,itt,it-1)
989                EXIT
990              END IF
991            END DO
992            IF (Indeppolychained) THEN
993              Ntracks(it) = Ntracks(it) + 1
994              ictrack = Ntracks(it)
995              ! Assigning all the IDs to the next step of the track
996              DO iip=1, NpolysIndep(i,it)
997                iiprev = polysIndep(i,iip,it)
998                tracks(1,iip,ictrack,it) = itrack
999                tracks(2,iip,ictrack,it) = iiprev
1000                tracks(3,iip,ictrack,it) = ctrpolys(1,iiprev,iit)
1001                tracks(4,iip,ictrack,it) = ctrpolys(2,iiprev,iit)
1002                tracks(5,iip,ictrack,it) = iit
1003              END DO
1004              EXIT
1005            END IF
1006            IF (Indeppolychained) EXIT
1007          END DO it1_tracks
1008
1009          ! Creation of a new track
1010          IF (.NOT.Indeppolychained) THEN
1011            Ntracks(it) = Ntracks(it) + 1
1012            ictrack = Ntracks(it)
1013            ! ID of new track
1014            maxtrack = maxtrack + 1
1015            IF (dbg) PRINT *,'  New track!', maxtrack
1016
1017            ! Assigning all the IDs to the next step of the track
1018            DO j=1, NpolysIndep(i,it)
1019              iiprev = polysIndep(i,j,it)
1020              tracks(1,j,ictrack,it) = maxtrack
1021              tracks(2,j,ictrack,it) = iiprev
1022              tracks(3,j,ictrack,it) = ctrpolys(1,iiprev,iit)
1023              tracks(4,j,ictrack,it) = ctrpolys(2,iiprev,iit)
1024              tracks(5,j,ictrack,it) = iit
1025            END DO
1026          END IF
1027
1028        END DO current_poly
1029
1030        IF (dbg) THEN
1031          PRINT *,'  At this time-step:', iit, ' N trajectories:', Ntracks(it)
1032          DO i=1, Ntracks(it)
1033            Nprev = COUNT(INT(tracks(2,:,i,it)) /= 0)
1034            PRINT *,i ,'ID tracks:', tracks(1,1,i,it), 'ID polygon:', tracks(2,1:Nprev,i,it)
1035          END DO
1036        END IF
1037
1038        CALL write_overlap_tracks_ascii(ftrackunit,iit,Nmaxpoly,Ntracks(it),tracks(:,:,1:Ntracks(it),it))
1039        ! Re-initializing for the next time-step
1040        tracks(:,:,:,it-1) = zeroRK
1041        Ntracks(it-1) = Ntracks(it)
1042        tracks(:,:,1:Ntracks(it-1),it-1) = tracks(:,:,1:Ntracks(it),it)
1043        Ntracks(it) = 0
1044        tracks(:,:,:,it) = zeroRK
1045
1046      END DO timesteps
1047      CLOSE(ftrackunit)
1048      IF (dbg) PRINT *,"  Succesful writting of ASCII chain of polygons 'trajectories_overlap.dat' !!"
1049      CLOSE(fprevunit)
1050    END IF
1051
1052    ! Summarizing trajectories
1053    ! When multiple polygons are available, the mean of their central positions determines the position
1054
1055    IF (doftracks) THEN
1056      ! ASCII file for the trajectories
1057      ftrackunit = freeunit()
1058      OPEN(ftrackunit, file='trajectories_overlap.dat', status='old', form='formatted', iostat=ios)
1059      msg = "Problems opening file: 'trajectories_overlap.dat'"
1060      CALL ErrMsg(msg,fname,ios)
1061
1062      ! ASCII file for the final trajectories
1063      ftrunit = freeunit()
1064      OPEN(ftrunit, file='trajectories.dat', status='new', form='formatted', iostat=ios)
1065      msg = "Problems opening file: 'trajectories.dat'"
1066      IF (ios == 17) PRINT *,"  Careful: 'trajectories.dat' already exists!!"
1067      CALL ErrMsg(msg,fname,ios)
1068
1069      finaltracks = zeroRK
1070
1071      DO itt=1, Nmaxtracks
1072        CALL read_overlap_single_track_ascii(ftrackunit, dt, Nmaxpoly, Nmaxtracks, itt, singletrack)
1073
1074        ! It might reach the las trajectory
1075        IF (ALL(singletrack == zeroRK)) EXIT
1076
1077        itrack = INT(MAXVAL(singletrack(1,1,:)))
1078        IF (dbg) THEN
1079          PRINT *,'  Trajectory:', itt, '_______', itrack
1080          DO it=1, dt
1081            IF (singletrack(2,1,it) /= zeroRK) THEN
1082              j = COUNT(singletrack(2,:,it) /= zeroRK)
1083              PRINT *,it,':',(singletrack(3,i,it),',',singletrack(4,i,it),' ; ',i=1,j)
1084            END IF
1085          END DO
1086        END IF
1087
1088        finaltracks = zeroRK
1089        finaltracks(1,:) = itrack*oneRK
1090        DO it =1, dt     
1091          Nprev = COUNT(INT(singletrack(2,:,it)) /= zeroRK)
1092          IF (Nprev /= 0) THEN
1093            finaltracks(5,it) = it*oneRK
1094            IF (TRIM(methodmulti) == 'largest') THEN
1095              maxarea = -10.*oneRK
1096              DO ip=1, Nprev
1097                IF (areapolys(singletrack(2,ip,it),it) > maxarea) THEN
1098                  maxarea = areapolys(singletrack(2,ip,it),it)
1099                  i = ip
1100                END IF
1101              END DO
1102              IF (dbg) THEN
1103                PRINT *,'  Determine the trajectory coordinates to the largest polygon:', i,          &
1104                  ' area:', maxarea
1105              END IF
1106              finaltracks(2,it) = singletrack(2,i,it)*oneRK
1107              finaltracks(3,it) = singletrack(3,i,it)
1108              finaltracks(4,it) = singletrack(4,i,it)
1109            ELSE IF (TRIM(methodmulti) == 'closest') THEN
1110              IF (it > 1) THEN
1111                mindist = 10000000.*oneRK
1112                DO ip=1, Nprev
1113                  dist = SQRT((singletrack(3,ip,it)-finaltracks(3,it-1))**2 +                         &
1114                    (singletrack(4,ip,it)-finaltracks(4,it-1))**2 )
1115                  IF (dist < mindist) THEN
1116                    mindist = dist
1117                    i = ip
1118                  END IF
1119                END DO
1120                finaltracks(2,it) = singletrack(3,i,it)*oneRK
1121                finaltracks(3,it) = singletrack(3,i,it)
1122                finaltracks(4,it) = singletrack(4,i,it)
1123                IF (dbg) THEN
1124                  PRINT *,'  Determine the trajectory coordinates to the closest previous polygon:',i,&
1125                    ' distance:', mindist
1126                END IF
1127              ELSE
1128                maxarea = -10.*oneRK
1129                DO ip=1, Nprev
1130                  IF (areapolys(singletrack(2,ip,it),it) > maxarea) THEN
1131                    maxarea = areapolys(singletrack(2,ip,it),it)
1132                    i = ip
1133                  END IF
1134                END DO
1135                IF (dbg) THEN
1136                  PRINT *, '  Determine the trajectory coordinates to the largest polygon:', i,        &
1137                    ' area:', maxarea, ' at the first time-step then to the closest'
1138                END IF
1139                finaltracks(2,it) = i*oneRK
1140                finaltracks(3,it) = singletrack(3,i,it)
1141                finaltracks(4,it) = singletrack(4,i,it)             
1142              END IF
1143            ELSE
1144              totArea = zeroRK
1145              finaltracks(2,it) = -oneRK
1146              finaltracks(3,it) = zeroRK
1147              finaltracks(4,it) = zeroRK
1148              DO ip=1, Nprev
1149                areai = areapolys(singletrack(2,ip,it),it)
1150                totArea = totArea + areai
1151                finaltracks(3,it) = finaltracks(3,it) + singletrack(3,ip,it)*areai
1152                finaltracks(4,it) = finaltracks(4,it) + singletrack(4,ip,it)*areai
1153              END DO
1154              finaltracks(3,it) = finaltracks(3,it)/totArea
1155              finaltracks(4,it) = finaltracks(4,it)/totArea
1156              IF (dbg) THEN
1157                PRINT *,'  Determine the trajectory coordinates to the area-averaged polygon ' //     &
1158                  ' total area:', totArea
1159              END IF
1160
1161            END IF
1162
1163          END IF
1164        END DO
1165        ! Writting the final track into the ASCII file
1166        CALL write_finaltrack_ascii(ftrunit, dt, finaltracks)
1167
1168      END DO
1169      CLOSE(ftrackunit)
1170      IF (dbg) PRINT *,"  Succesful writting of ASCII trajectories 'trajectories.dat' !!"
1171      CLOSE(ftrunit)
1172    END IF
1173
1174    IF (ALLOCATED(coins)) DEALLOCATE(coins)
1175    IF (ALLOCATED(coinsNpts)) DEALLOCATE(coinsNpts)
1176
1177    RETURN
1178
1179  END SUBROUTINE poly_overlap_tracks_area_ascii
1180
1181  SUBROUTINE poly_overlap_tracks_area(dbg, dx, dy, dt, minarea, inNallpolys, allpolys, ctrpolys,      &
1182    areapolys, Nmaxpoly, Nmaxtracks, tracks, finaltracks)
1183! Subroutine to determine tracks of a series of consecutive 2D field with polygons using maximum
1184!   overlaping/coincidence filtrered by a minimal area
1185
1186    IMPLICIT NONE
1187
1188    LOGICAL, INTENT(in)                                  :: dbg
1189    INTEGER, INTENT(in)                                  :: dx, dy, dt, Nmaxpoly, Nmaxtracks
1190    INTEGER, DIMENSION(dt), INTENT(in)                   :: inNallpolys
1191    INTEGER, DIMENSION(dx,dy,dt), INTENT(in)             :: allpolys
1192    REAL(r_k), INTENT(in)                                :: minarea
1193    REAL(r_k), DIMENSION(2,Nmaxpoly,dt), INTENT(in)      :: ctrpolys
1194    REAL(r_k), DIMENSION(Nmaxpoly,dt), INTENT(in)        :: areapolys
1195    REAL(r_k), DIMENSION(5,Nmaxpoly,Nmaxtracks,dt),                                                   &
1196      INTENT(out)                                        :: tracks
1197    REAL(r_k), DIMENSION(4,Nmaxtracks,dt), INTENT(out)   :: finaltracks
1198
1199! Local
1200    INTEGER                                              :: i, j, ip, it, iip, itt
1201    INTEGER                                              :: ierr
1202    REAL(r_k), DIMENSION(Nmaxpoly)                       :: Aprevpolys, Acurrpolys
1203    REAL(r_k), DIMENSION(2,Nmaxpoly)                     :: Cprevpolys, Ccurrpolys
1204    INTEGER, DIMENSION(dt)                               :: Nallpolys
1205    INTEGER, DIMENSION(dx,dy)                            :: meetpolys, searchpolys
1206    INTEGER, DIMENSION(Nmaxpoly)                         :: coincidencies
1207    INTEGER, DIMENSION(Nmaxpoly)                         :: prevID, currID
1208    INTEGER, DIMENSION(:), ALLOCATABLE                   :: coins
1209    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: coinsNpts
1210    INTEGER                                              :: Nmeet, Nsearch, Nindep
1211    INTEGER, DIMENSION(dt)                               :: Nindeppolys
1212    CHARACTER(len=5)                                     :: NcoinS
1213    INTEGER, DIMENSION(Nmaxpoly,Nmaxpoly,dt)             :: polysIndep
1214    INTEGER, DIMENSION(Nmaxpoly,dt)                      :: NpolysIndep
1215    INTEGER, DIMENSION(Nmaxpoly,dt)                      :: SpolysIndep
1216    INTEGER                                              :: iindep, iiprev
1217    INTEGER                                              :: Nprev, NNprev, Ntprev
1218    LOGICAL                                              :: Indeppolychained
1219    INTEGER                                              :: itrack, ictrack
1220    REAL(r_k)                                            :: ixp, iyp
1221    INTEGER                                              :: ttrack
1222    INTEGER, DIMENSION(dt)                               :: Ntracks
1223    INTEGER                                              :: idtrack, maxtrack
1224
1225!!!!!!! Variables
1226! dx,dy,dt: space/time dimensions
1227! Nallpolys: Vector with the number of polygons at each time-step
1228! allpolys: Series of 2D field with the polygons
1229! minarea: minimal area (in same units as areapolys) to perform the tracking
1230! ctrpolys: center of the polygons
1231! areapolys: area of the polygons
1232! Nmaxpoly: Maximum possible number of polygons
1233! Nmaxtracks: maximum number of tracks
1234! tracks: series of consecutive polygons
1235! trackperiod: period of the track in time-steps
1236
1237    fname = 'poly_overlap_tracks_area'
1238
1239    IF (dbg) PRINT *,TRIM(fname)
1240
1241    ! Number of independent polygons by time step
1242    Nindeppolys = 0
1243    ! Number of polygons attached to each independent polygons by time step
1244    NpolysIndep = 0
1245    ! ID of searching polygon attached to each independent polygons by time step
1246    SpolysIndep = 0
1247    ! ID of polygons attached to each independent polygons by time step
1248    polysIndep = 0
1249    ! ID of polygons from previous time-step
1250    prevID = 0
1251    ! ID of polygons from current time-step
1252    currID = 0
1253
1254    ! First time-step all are independent polygons
1255    it = 1
1256    Nmeet = inNallpolys(it)
1257    Nindeppolys(it) = Nmeet
1258    ip = 0
1259    meetpolys = allpolys(:,:,it)
1260    DO i=1, Nmeet
1261      IF (areapolys(i,it) >= minarea) THEN
1262        ip = ip + 1
1263        SpolysIndep(ip,it) = i
1264        currID(ip) = i
1265        Acurrpolys(ip) = areapolys(i,it)
1266        Ccurrpolys(1,ip) = ctrpolys(1,i,it)
1267        Ccurrpolys(2,ip) = ctrpolys(2,i,it)
1268        NpolysIndep(ip,it) = 1
1269        polysIndep(ip,1,it) = i
1270      ELSE
1271        WHERE (meetpolys == i)
1272          meetpolys = 0
1273        END WHERE
1274      END IF
1275    END DO
1276    Nallpolys(1) = ip
1277    Nindeppolys(1) = ip
1278
1279    ! Starting step
1280    it = 0
1281    IF (dbg) THEN
1282      PRINT *,'  time step:',it+1,' number to look polygons:', Nmeet,' searching polygons:',0
1283      PRINT *,'    number of independent polygons:', Nindeppolys(it+1)
1284      PRINT *,'    indep_polygon prev_step_polygon Nassociated_polygons curr_ass_polygons _______'
1285      DO i=1, Nindeppolys(it+1)
1286        PRINT *,i, SpolysIndep(i,it+1), NpolysIndep(i,it+1), ':',                                     &
1287          polysIndep(i,1:NpolysIndep(i,it+1),it+1)
1288      END DO
1289    END IF
1290
1291    ! Looking for the coincidencies at each time step
1292    DO it=1, dt-1
1293      ! Number of times that a polygon has a coincidence
1294      coincidencies = 0
1295
1296      Nmeet = inNallpolys(it+1)
1297      searchpolys = meetpolys
1298      meetpolys = allpolys(:,:,it+1)
1299      prevID = 0
1300      prevID = currID
1301      Aprevpolys = Acurrpolys
1302      Cprevpolys = Ccurrpolys
1303      ip = 0
1304
1305      DO i=1, Nmeet
1306        IF (areapolys(i,it+1) >= minarea) THEN
1307          ip = ip + 1
1308          currID(ip) = i
1309          Acurrpolys(ip) = areapolys(i,it+1)
1310          Acurrpolys(ip) = areapolys(i,it+1)
1311          Ccurrpolys(1,ip) = ctrpolys(1,i,it+1)
1312          Ccurrpolys(2,ip) = ctrpolys(2,i,it+1)
1313        ELSE
1314          WHERE (meetpolys == i)
1315            meetpolys = 0
1316          END WHERE
1317        END IF
1318      END DO
1319      Nallpolys(it+1) = ip
1320      Nindeppolys(it+1) = ip
1321
1322      Nmeet = Nallpolys(it+1)
1323      ! Looking throughout the independent polygons
1324      Nsearch = Nindeppolys(it)
1325
1326      IF (ALLOCATED(coins)) DEALLOCATE(coins)
1327      ALLOCATE(coins(Nmeet), STAT=ierr)
1328      msg="Problems allocating 'coins'"
1329      CALL ErrMsg(msg,fname,ierr)
1330
1331      IF (ALLOCATED(coinsNpts)) DEALLOCATE(coinsNpts)
1332      ALLOCATE(coinsNpts(Nmeet, Nsearch), STAT=ierr)
1333      msg="Problems allocating 'coinsNpts'"
1334      CALL ErrMsg(msg,fname,ierr)
1335
1336      CALL coincidence_all_polys_area(dbg, dx,dy, Nmeet, currID, meetpolys, Acurrpolys(1:Nmeet),      &
1337        Nsearch, prevID, searchpolys, Cprevpolys(:,1:Nsearch), Aprevpolys(1:Nsearch), coins,          &
1338        coinsNpts)
1339
1340      ! Counting the number of times that a polygon has a coincidency
1341      IF (dbg) THEN
1342        PRINT *,'  Coincidencies for the given time-step:', it+1,' _______'
1343        DO i=1, Nmeet
1344          PRINT *,currID(i), coins(i),' N search pts:', coinsNpts(i,:)
1345        END DO
1346      END IF
1347
1348      ! Looking for the same equivalencies
1349      Nindep = 0
1350      DO i=1, Nmeet
1351        IF (coins(i) == -1) THEN
1352          Nindep = Nindep + 1
1353          SpolysIndep(Nindep,it+1) = -1
1354          NpolysIndep(Nindep,it+1) = NpolysIndep(Nindep,it+1) + 1
1355          polysIndep(Nindep,NpolysIndep(Nindep,it+1),it+1) = currID(i)
1356        ELSE IF (coins(i) == -9) THEN
1357          WRITE(NcoinS,'(I5)')coins(i)
1358          msg="coins= "//TRIM(NcoinS)//" This is an error. One should have always only one " //      &
1359            "coincidence of polygon"
1360          CALL ErrMsg(msg, fname, -1)
1361        ELSE
1362          ! Looking for coincidences with previous independent polygons
1363          DO ip=1, Nsearch
1364            ! Looking into the polygons associated
1365            NNprev = NpolysIndep(ip,it)
1366            DO j=1, NNprev
1367              IF (coins(i) == polysIndep(ip,j,it)) THEN
1368                ! Which index corresponds to this coincidence?
1369                iindep = Index1DArrayI(SpolysIndep(1:Nindep,it+1), Nindep, coins(i))
1370                IF (iindep == -1) THEN
1371                  Nindep = Nindep + 1
1372                  SpolysIndep(Nindep,it+1) = coins(i)
1373                END IF
1374                iindep = Index1DArrayI(SpolysIndep(1:Nindep,it+1), Nindep, coins(i))
1375                IF (iindep < 0) THEN
1376                  PRINT *,'    Looking for:', coins(i)
1377                  PRINT *,'    Within:', SpolysIndep(1:Nindep,it+1)
1378                  PRINT *,'    Might content:', polysIndep(ip,1:NNprev,it)
1379                  PRINT *,'    From an initial list:', coins(1:Nmeet)
1380                  msg = 'Wrong index! There must be an index here'
1381                  CALL ErrMsg(msg,fname,iindep)
1382                END IF
1383                coincidencies(ip) = coincidencies(ip) + 1
1384                NpolysIndep(iindep,it+1) = NpolysIndep(iindep,it+1) + 1
1385                polysIndep(iindep,NpolysIndep(iindep,it+1),it+1) = currID(i)
1386                EXIT
1387              END IF
1388            END DO
1389          END DO
1390        END IF
1391      END DO
1392      Nindeppolys(it+1) = Nindep
1393
1394      IF (dbg) THEN
1395        PRINT *,'  time step:',it+1,' number to look polygons:', Nmeet,' searching polygons:',Nsearch
1396        PRINT *,'    number of independent polygons:', Nindeppolys(it+1)
1397        PRINT *,'    indep_polygon prev_step_polygon Nassociated_polygons curr_ass_polygons _______'
1398        DO i=1, Nindeppolys(it+1)
1399          PRINT *,i, SpolysIndep(i,it+1), NpolysIndep(i,it+1), ':',                                   &
1400            polysIndep(i,1:NpolysIndep(i,it+1),it+1)
1401        END DO
1402      END IF
1403    END DO
1404
1405    IF (dbg) THEN
1406      PRINT *,  'Coincidencies to connect _______'
1407      DO it=1, dt
1408        PRINT *,'  it:', it, ' Nindep:', Nindeppolys(it)
1409        PRINT '(4x,3(A6,1x))','Nindep', 'PrevID', 'IDs'
1410        DO ip=1, Nindeppolys(it)
1411          PRINT '(4x,I6,A1,I6,A1,100(I6))', ip, ',', SpolysIndep(ip,it), ':',                         &
1412            polysIndep(ip,1:NpolysIndep(ip,it),it)
1413        END DO
1414      END DO
1415
1416    END IF
1417
1418    ! Trajectories
1419    ! It should be done following the number of 'independent' polygons
1420    ! One would concatenate that independent polygons which share IDs from one step to another
1421
1422    ! First time-step. Take all polygons
1423    itrack = 0
1424    tracks = 0.
1425    Ntracks = 0
1426    DO ip=1, Nindeppolys(1)
1427      itrack = itrack + 1
1428      tracks(1,1,itrack,1) = itrack*1.
1429      tracks(2,1,itrack,1) = SpolysIndep(ip,1)
1430      tracks(3,1,itrack,1) = ctrpolys(1,ip,1)
1431      tracks(4,1,itrack,1) = ctrpolys(2,ip,1)
1432      tracks(5,1,itrack,1) = 1
1433      Ntracks(1) = Ntracks(1) + 1
1434    END DO
1435
1436    ! Looping allover already assigned tracks
1437    timesteps: DO it=2, dt
1438      IF (dbg) PRINT *,'track-timestep:', it, 'N indep polys:', Nindeppolys(it)
1439      ! Indep polygons current time-step
1440      current_poly: DO i=1, Nindeppolys(it)
1441        IF (dbg) PRINT *,'  curent poly:', i, 'Prev poly:', SpolysIndep(i,it), ' N ass. polygons:',   &
1442          NpolysIndep(i,it), 'ass. poly:', polysIndep(i,1:NpolysIndep(i,it),it)
1443        Indeppolychained = .FALSE.
1444
1445        ! Number of tracks previous time-step
1446        ! Looping overall
1447        it1_tracks: DO itt=1, Ntracks(it-1)
1448          itrack = tracks(1,1,itt,it-1)
1449          ! Number polygons ID assigned
1450          Ntprev = COUNT(tracks(2,:,itt,it-1) /= 0)
1451          IF (dbg) PRINT *,itt,'  track:', itrack, 'assigned:', tracks(2,1:Ntprev,itt,it-1)
1452
1453          ! Looking for coincidencies
1454          DO iip=1, Ntprev
1455            IF (tracks(2,iip,itt,it-1) == SpolysIndep(i,it)) THEN
1456              Indeppolychained = .TRUE.
1457              IF (dbg) PRINT *,'    coincidence found by polygon:', tracks(2,iip,itt,it-1)
1458              EXIT
1459            END IF
1460          END DO
1461          IF (Indeppolychained) THEN
1462            Ntracks(it) = Ntracks(it) + 1
1463            ictrack = Ntracks(it)
1464            ! Assigning all the IDs to the next step of the track
1465            DO iip=1, NpolysIndep(i,it)
1466              iiprev = polysIndep(i,iip,it)
1467              tracks(1,iip,ictrack,it) = itrack
1468              tracks(2,iip,ictrack,it) = iiprev
1469              ixp = ctrpolys(1,iiprev,it)
1470              iyp = ctrpolys(2,iiprev,it)
1471              tracks(3,iip,ictrack,it) = ixp
1472              tracks(4,iip,ictrack,it) = iyp
1473              tracks(5,iip,ictrack,it) = it
1474            END DO
1475            EXIT
1476          END IF
1477          IF (Indeppolychained) EXIT
1478        END DO it1_tracks
1479
1480        ! Creation of a new track
1481        IF (.NOT.Indeppolychained) THEN
1482          Ntracks(it) = Ntracks(it) + 1
1483          ictrack = Ntracks(it)
1484          ! ID of new track
1485          maxtrack = INT(MAXVAL(tracks(1,:,:,:)*1.))
1486          IF (dbg) PRINT *,'  New track!', maxtrack+1
1487
1488          ! Assigning all the IDs to the next step of the track
1489          DO j=1, NpolysIndep(i,it)
1490            iiprev = polysIndep(i,j,it)
1491            tracks(1,j,ictrack,it) = maxtrack+1
1492            tracks(2,j,ictrack,it) = iiprev
1493            ixp = ctrpolys(1,iiprev,it)
1494            iyp = ctrpolys(2,iiprev,it)
1495            tracks(3,j,ictrack,it) = ixp
1496            tracks(4,j,ictrack,it) = iyp
1497            tracks(5,j,ictrack,it) = it
1498          END DO
1499        END IF
1500
1501      END DO current_poly
1502
1503      IF (dbg) THEN
1504        PRINT *,'  At this time-step:', it, ' N trajectories:', Ntracks(it)
1505        DO i=1, Ntracks(it)
1506          Nprev = COUNT(INT(tracks(2,:,i,it)) /= 0)
1507          PRINT *,i ,'ID tracks:', tracks(1,1,i,it), 'ID polygon:', tracks(2,1:Nprev,i,it)
1508        END DO
1509      END IF
1510
1511    END DO timesteps
1512
1513    ! Summarizing trajectories
1514    ! When multiple polygons are available, the mean of their central positions determines the position
1515
1516    finaltracks = 0.
1517    maxtrack = MAXVAL(tracks(1,:,:,:))
1518
1519    DO it=1, dt
1520      DO itt=1, Ntracks(it)
1521        itrack = INT(tracks(1,1,itt,it))
1522        Nprev = COUNT(INT(tracks(2,:,itt,it)) /= 0)
1523        finaltracks(1,itrack,it) = itrack*1.
1524        finaltracks(2,itrack,it) = SUM(tracks(3,:,itt,it))/Nprev*1.
1525        finaltracks(3,itrack,it) = SUM(tracks(4,:,itt,it))/Nprev*1.
1526        finaltracks(4,itrack,it) = it*1.
1527      END DO
1528    END DO
1529
1530    DEALLOCATE(coins)
1531    DEALLOCATE(coinsNpts)
1532
1533    RETURN
1534
1535  END SUBROUTINE poly_overlap_tracks_area
1536
1537  SUBROUTINE coincidence_all_polys_area(dbg, dx, dy, Nallpoly, IDallpoly, allpoly, icpolys, Npoly, &
1538    IDpolys, polys, cpolys, apolys, polycoins, coinNptss)
1539! Subtourine to determine which is the coincident polygon when a boolean polygon is provided to a map of integer polygons
1540!   In case of multiple coincidencies, the closest and then the largest is taken filtrered by a minimal area
1541!   Here the difference is that the index does not coincide with its ID
1542
1543    IMPLICIT NONE
1544
1545    LOGICAL, INTENT(in)                                  :: dbg
1546    INTEGER, INTENT(in)                                  :: dx, dy, Nallpoly, Npoly
1547    INTEGER, DIMENSION(dx,dy), INTENT(in)                :: allpoly, polys
1548    INTEGER, DIMENSION(Nallpoly), INTENT(in)             :: IDallpoly
1549    INTEGER, DIMENSION(Npoly), INTENT(in)                :: IDpolys
1550    REAL(r_k), DIMENSION(2,Nallpoly), INTENT(in)         :: icpolys
1551    REAL(r_k), DIMENSION(2,Npoly), INTENT(in)            :: cpolys
1552    REAL(r_k), DIMENSION(Npoly), INTENT(in)              :: apolys
1553    INTEGER, DIMENSION(Nallpoly), INTENT(out)            :: polycoins
1554    INTEGER, DIMENSION(Nallpoly,Npoly), INTENT(out)      :: coinNptss
1555
1556! Local
1557    INTEGER                                              :: i, j, ip
1558    INTEGER                                              :: maxcorr
1559    INTEGER                                              :: Nmaxcorr
1560    LOGICAL, DIMENSION(dx,dy)                            :: boolpoly
1561    INTEGER                                              :: maxcoin
1562    REAL                                                 :: dist, maxcoindist, maxcoinarea
1563    INTEGER, DIMENSION(Npoly)                            :: IDcoins
1564
1565!!!!!!! Variables
1566! dx,dy: dimension of the space
1567! Nallpoly: Number of polygons to find coincidence
1568! allpoly: space with the polygons to meet
1569! IDallpoly: ID of the polygon to find coincidence
1570! icpolys: center of the polygons to look for the coincidence
1571! Npoly: number of polygons on the 2D space
1572! polys: 2D field of polygons identified by their integer number (0 for no polygon)
1573! IDpolys: ID of the polygon to search for coincidences
1574! cpolys: center of the polygons
1575! apolys: area of the polygons
1576! polycoins: coincident polyogn
1577!          -1: no-coincidence
1578!   1 < Npoly: single coincidence with a given polygon
1579!          -9: coincidence with more than one polygon
1580! coinNptss: number of points coincident with each polygon
1581
1582    fname = 'coincidence_all_polys_area'
1583    IF (dbg) PRINT *,TRIM(fname)
1584
1585    DO ip=1, Nallpoly
1586      boolpoly = allpoly == IDallpoly(ip)
1587      CALL coincidence_poly_area(dbg, dx, dy, boolpoly, Npoly, polys, polycoins(ip), IDcoins,         &
1588        coinNptss(ip,:))
1589      IF (dbg) PRINT *,'  polygon', IDallpoly(ip), ' coincidence with:', polycoins(ip), 'IDpolys:', IDpolys(1:Npoly)
1590
1591      ! Coincidence with more than one polygon
1592      IF (polycoins(ip) == -9) THEN
1593        maxcoindist = -10.
1594        maxcoinarea = -10.
1595        maxcoin = MAXVAL(coinNptss(ip,:))
1596        DO j=1, Npoly
1597          IF (coinNptss(ip,j) == maxcoin) THEN
1598            dist = SQRT( (icpolys(1,ip)*1.-cpolys(1,j)*1.)**2 + (icpolys(2,ip)*1.-cpolys(2,j)*1.)**2 )
1599            IF ( dist > maxcoindist) THEN
1600              maxcoindist = dist
1601              maxcoinarea = apolys(j)
1602              polycoins(ip) = IDcoins(j)
1603            ELSE IF ( dist == maxcoindist) THEN
1604              IF (apolys(j) > maxcoinarea) THEN
1605                polycoins(ip) = IDcoins(j)
1606                maxcoinarea = apolys(j)
1607              END IF
1608            END IF
1609          END IF
1610        END DO
1611      END IF
1612    END DO
1613
1614    RETURN
1615
1616  END SUBROUTINE coincidence_all_polys_area
1617
1618  SUBROUTINE coincidence_poly_area(dbg, dx, dy, poly, Npoly, polys, polycoin, IDpoly, coinNpts)
1619! Subtourine to determine which is the coincident polygon when a boolean polygon is provided to a map of integer polygons
1620!   Here the difference is that the index does not coincide with its ID
1621
1622    IMPLICIT NONE
1623
1624    LOGICAL, INTENT(in)                                  :: dbg
1625    INTEGER, INTENT(in)                                  :: dx, dy, Npoly
1626    LOGICAL, DIMENSION(dx,dy), INTENT(in)                :: poly
1627    INTEGER, DIMENSION(dx,dy), INTENT(in)                :: polys
1628    INTEGER, INTENT(out)                                 :: polycoin
1629    INTEGER, DIMENSION(Npoly), INTENT(out)               :: IDpoly, coinNpts
1630
1631! Local
1632    INTEGER                                              :: i, j, ip
1633    INTEGER                                              :: maxcorr
1634    INTEGER                                              :: Nmaxcorr
1635! Lluis
1636    INTEGER                                              :: Ndiffvals
1637    INTEGER, DIMENSION(:), ALLOCATABLE                   :: diffvals
1638
1639!!!!!!! Variables
1640! dx,dy: dimension of the space
1641! poly: bolean polygon to meet
1642! Npoly: number of polygons on the 2D space
1643! polys: 2D field of polygons identified by their integer number (0 for no polygon)
1644! polycoin: coincident polyogn
1645!          -1: no-coincidence
1646!   1 < Npoly: single coincidence with a given polygon
1647!          -9: coincidence with more than one polygon
1648! IDpoly: ID of the found polygon
1649! coinNpts: number of points coincident with each polygon
1650
1651    fname = 'coincidence_poly_area'
1652    IF (dbg) PRINT *,TRIM(fname)
1653
1654    IF (dbg) THEN
1655      PRINT *,'  Boolean polygon to search coincidences ...'
1656      DO i=1,dx
1657        PRINT *,poly(i,:)
1658      END DO
1659
1660      PRINT *,'  2D polygons space ...'
1661      DO i=1,dx
1662        PRINT '(1000(I7,1x))',polys(i,:)
1663      END DO
1664    END IF
1665
1666    IF (ALLOCATED(diffvals)) DEALLOCATE(diffvals)
1667    ALLOCATE(diffvals(dx*dy))
1668
1669    ! Checking for consistency on number of polygons and real content (except 0 value)
1670    CALL Nvalues_2DArrayI(dx, dy, dx*dy, polys, Ndiffvals, diffvals)
1671    IF (Ndiffvals -1 /= Npoly) THEN
1672      PRINT *,TRIM(emsg)
1673      PRINT *,'    number of different values:', Ndiffvals-1, ' theoretical Npoly:', Npoly
1674      PRINT *,'    Different values:', diffvals(1:Ndiffvals)
1675      msg = 'Number of different values and Npoly must coincide'
1676      CALL ErrMsg(msg, fname, -1)
1677    END IF
1678
1679    ! Looking for coincient points for the polygon
1680    coinNpts = 0
1681    IDpoly = 0
1682    ip = 0
1683    DO i=1,dx
1684      DO j=1,dy
1685        IF (poly(i,j) .AND. polys(i,j) .NE. 0) THEN
1686          IF (.NOT.ANY(IDpoly == polys(i,j))) THEN
1687            ip = ip + 1
1688            IDpoly(ip) = polys(i,j)
1689          ELSE
1690            ip = Index1DarrayI(IDpoly, Npoly, polys(i,j))
1691          END IF
1692          coinNpts(ip) = coinNpts(ip) + 1
1693        END IF
1694      END DO
1695    END DO
1696
1697    maxcorr = 0
1698    maxcorr = INT(MAXVAL(coinNpts*1.))
1699
1700    IF (dbg) PRINT *,'  Maximum coincidence:', maxcorr
1701    IF (maxcorr == 0) THEN
1702      polycoin = -1
1703    ELSE
1704      Nmaxcorr = 0
1705      DO ip=1, Npoly
1706        IF (coinNpts(ip) == maxcorr) THEN
1707          Nmaxcorr = Nmaxcorr+1
1708          polycoin = IDpoly(ip)
1709        END IF
1710      END DO
1711      IF (Nmaxcorr > 1) polycoin = -9
1712    END IF
1713
1714    IF (dbg) THEN
1715      PRINT *,'  Coincidences for each polygon _______', Npoly
1716      DO ip=1, Npoly
1717        PRINT *,'  ',ip, ' ID:', IDpoly(ip),': ', coinNpts(ip)
1718      END DO
1719    END IF
1720
1721    RETURN
1722
1723END SUBROUTINE coincidence_poly_area
1724
1725  SUBROUTINE poly_overlap_tracks(dbg, dx, dy, dt, minarea, Nallpolys, allpolys, ctrpolys,        &
1726    areapolys, Nmaxpoly, Nmaxtracks, tracks, finaltracks)
1727! Subroutine to determine tracks of a series of consecutive 2D field with polygons using maximum overlaping/coincidence
1728
1729    IMPLICIT NONE
1730
1731    LOGICAL, INTENT(in)                                  :: dbg
1732    INTEGER, INTENT(in)                                  :: dx, dy, dt, Nmaxpoly, Nmaxtracks
1733    INTEGER, DIMENSION(dt), INTENT(in)                   :: Nallpolys
1734    INTEGER, DIMENSION(dx,dy,dt), INTENT(in)             :: allpolys
1735    REAL(r_k), INTENT(in)                                :: minarea
1736    REAL(r_k), DIMENSION(2,Nmaxpoly,dt), INTENT(in)      :: ctrpolys
1737    REAL(r_k), DIMENSION(Nmaxpoly,dt), INTENT(in)        :: areapolys
1738    REAL(r_k), DIMENSION(5,Nmaxpoly,Nmaxtracks,dt),                                                   &
1739      INTENT(out)                                        :: tracks
1740    REAL(r_k), DIMENSION(4,Nmaxtracks,dt), INTENT(out)   :: finaltracks
1741
1742! Local
1743    INTEGER                                              :: i, j, ip, it, iip, itt
1744    INTEGER                                              :: ierr
1745    INTEGER, DIMENSION(Nmaxpoly,dt)                      :: coincidencies, NOcoincidencies
1746    INTEGER, DIMENSION(:), ALLOCATABLE                   :: coins
1747    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: coinsNpts
1748    INTEGER, DIMENSION(Nmaxpoly,dt)                      :: polycoincidencies
1749    INTEGER, DIMENSION(Nmaxpoly,Nmaxpoly,dt)             :: coincidenciesNpts
1750    INTEGER                                              :: Nmeet, Nsearch, Nindep
1751    INTEGER, DIMENSION(dt)                               :: Nindeppolys
1752    CHARACTER(len=5)                                     :: NcoinS
1753    INTEGER, DIMENSION(Nmaxpoly,Nmaxpoly,dt)             :: polysIndep
1754    INTEGER, DIMENSION(Nmaxpoly,dt)                      :: NpolysIndep
1755    INTEGER, DIMENSION(Nmaxpoly,dt)                      :: SpolysIndep
1756    INTEGER                                              :: iindep, iiprev
1757    INTEGER                                              :: Nprev, NNprev, Ntprev
1758    LOGICAL                                              :: Indeppolychained
1759    INTEGER                                              :: itrack, ictrack
1760    INTEGER                                              :: ixp, iyp, ttrack
1761    INTEGER, DIMENSION(dt)                               :: Ntracks
1762    INTEGER                                              :: idtrack, maxtrack
1763
1764!!!!!!! Variables
1765! dx,dy,dt: space/time dimensions
1766! Nallpolys: Vector with the number of polygons at each time-step
1767! allpolys: Series of 2D field with the polygons
1768! minarea: minimal area (in same units as areapolys) to perform the tracking
1769! ctrpolys: center of the polygons
1770! areapolys: area of the polygons
1771! Nmaxpoly: Maximum possible number of polygons
1772! Nmaxtracks: maximum number of tracks
1773! tracks: series of consecutive polygons
1774! trackperiod: period of the track in time-steps
1775
1776    fname = 'poly_overlap_tracks'
1777
1778    IF (dbg) PRINT *,TRIM(fname)
1779
1780    polycoincidencies = fillvalI
1781    coincidenciesNpts = fillvalI
1782    ! Number of times that a polygon has a coincidence
1783    coincidencies = 0
1784    ! Polygons without a coincidence
1785    NOcoincidencies = 0
1786    ! Number of independent polygons by time step
1787    Nindeppolys = 0
1788    ! Number of polygons attached to each independent polygons by time step
1789    NpolysIndep = 0
1790    ! ID of searching polygon attached to each independent polygons by time step
1791    SpolysIndep = 0
1792    ! ID of polygons attached to each independent polygons by time step
1793    polysIndep = 0
1794
1795    ! First time-step all are independent polygons
1796    it = 1
1797    Nmeet = Nallpolys(it)
1798    Nindeppolys(it) = Nmeet
1799    DO i=1, Nmeet
1800      SpolysIndep(i,it) = i
1801      NpolysIndep(1:Nmeet,it) = 1
1802      polysIndep(1,i,it) = i
1803    END DO
1804
1805    ! Looking for the coincidencies at each time step
1806    DO it=1, dt-1
1807      Nmeet = Nallpolys(it+1)
1808      Nsearch = Nallpolys(it)
1809
1810      IF (ALLOCATED(coins)) DEALLOCATE(coins)
1811      ALLOCATE(coins(Nmeet), STAT=ierr)
1812      msg="Problems allocating 'coins'"
1813      CALL ErrMsg(msg,fname,ierr)
1814
1815      IF (ALLOCATED(coinsNpts)) DEALLOCATE(coinsNpts)
1816      ALLOCATE(coinsNpts(Nmeet, Nsearch), STAT=ierr)
1817      msg="Problems allocating 'coinsNpts'"
1818      CALL ErrMsg(msg,fname,ierr)
1819
1820      CALL coincidence_all_polys(dbg, dx, dy, Nmeet, allpolys(:,:,it+1), ctrpolys(:,1:Nmeet,it+1),    &
1821        Nsearch, allpolys(:,:,it), ctrpolys(:,1:Nsearch,it), areapolys(1:Nsearch,it), coins, coinsNpts)
1822
1823      polycoincidencies(1:Nmeet,it+1) = coins
1824      coincidenciesNpts(1:Nmeet,1:Nsearch,it+1) = coinsNpts
1825
1826      ! Counting the number of times that a polygon has a coincidency
1827      IF (dbg) THEN
1828        PRINT *,'  Coincidencies for the given time-step:', it+1,' _______'
1829        DO i=1, Nmeet
1830          PRINT *,coins(i),' N search pts:', coinsNpts(i,:)
1831        END DO
1832      END IF
1833
1834      Nindep = 0
1835      DO i=1, Nmeet
1836        IF (coins(i) == -1) THEN
1837          Nindep = Nindep + 1
1838          NOcoincidencies(i,it+1) = 1
1839          SpolysIndep(Nindep,it+1) = -1
1840          NpolysIndep(Nindep,it+1) = NpolysIndep(Nindep,it+1) + 1
1841          polysIndep(Nindep,NpolysIndep(Nindep,it+1),it+1) = i
1842        ELSE IF (coins(i) == -9) THEN
1843          WRITE(NcoinS,'(I5)')coins(i)
1844          msg="coins= "//TRIM(NcoinS)//" This is an error. One should have always only one " //      &
1845            "coincidence of polygon"
1846          CALL ErrMsg(msg, fname, -1)
1847        ELSE
1848          DO ip=1, Nsearch
1849            IF (coins(i) == ip) THEN
1850              IF (coincidencies(ip,it+1) == 0) THEN
1851                Nindep = Nindep + 1
1852                SpolysIndep(Nindep,it+1) = ip
1853              END IF
1854              coincidencies(ip,it+1) = coincidencies(ip,it+1) + 1
1855              DO iindep=1, Nindep
1856                IF (SpolysIndep(iindep,it+1) == coins(i)) THEN
1857                  NpolysIndep(iindep,it+1) = NpolysIndep(iindep,it+1) + 1
1858                  polysIndep(iindep,NpolysIndep(iindep,it+1),it+1) = i
1859                END IF
1860              END DO
1861            END IF
1862          END DO
1863        END IF
1864      END DO
1865      Nindeppolys(it+1) = Nindep
1866
1867      IF (dbg) THEN
1868        PRINT *,'  time step:',it+1,' number to look polygons:', Nmeet,' searching polygons:',Nsearch
1869        PRINT *,'    number of independent polygons:', Nindeppolys(it+1)
1870        PRINT *,'    indep_polygon prev_step_polygon Nassociated_polygons curr_ass_polygons _______'
1871        DO i=1, Nindeppolys(it+1)
1872          PRINT *,i, SpolysIndep(i,it+1), NpolysIndep(i,it+1), ':',                                   &
1873            polysIndep(i,1:NpolysIndep(i,it+1),it+1)
1874        END DO
1875      END IF
1876    END DO
1877
1878    IF (dbg) THEN
1879      PRINT *,  'Coincidencies to connect _______'
1880      DO it=1, dt
1881        PRINT *,'  it:', it, ' Nindep:', Nindeppolys(it)
1882        PRINT '(4x,3(A6,1x))','Nindep', 'PrevID', 'IDs'
1883        DO ip=1, Nindeppolys(it)
1884          PRINT '(4x,I6,A1,I6,A1,100(I6))', ip, ',', SpolysIndep(ip,it), ':',                         &
1885            polysIndep(ip,1:NpolysIndep(ip,it),it)
1886        END DO
1887      END DO
1888
1889    END IF
1890
1891    ! Trajectories
1892    ! It should be done following the number of 'independent' polygons
1893    ! One would concatenate that independent polygons which share IDs from one step to another
1894
1895    ! First time-step. Take all polygons
1896    itrack = 0
1897    tracks = 0.
1898    Ntracks = 0
1899    DO ip=1, Nindeppolys(1)
1900      itrack = itrack + 1
1901      tracks(1,1,itrack,1) = itrack*1.
1902      tracks(2,1,itrack,1) = SpolysIndep(ip,1)
1903      tracks(3,1,itrack,1) = ctrpolys(1,ip,1)
1904      tracks(4,1,itrack,1) = ctrpolys(2,ip,1)
1905      tracks(5,1,itrack,1) = 1
1906      Ntracks(1) = Ntracks(1) + 1
1907    END DO
1908
1909    ! Looping allover already assigned tracks
1910    timesteps: DO it=2, dt
1911      IF (dbg) PRINT *,'timestep:', it, 'N indep polys:', Nindeppolys(it)
1912      ! Indep polygons current time-step
1913      current_poly: DO i=1, Nindeppolys(it)
1914        IF (dbg) PRINT *,'  curent poly:', i, 'Prev poly:', SpolysIndep(i,it), ' N ass. polygons:',   &
1915          NpolysIndep(i,it), 'ass. poly:', polysIndep(i,1:NpolysIndep(i,it),it)
1916        Indeppolychained = .FALSE.
1917
1918        ! Number of tracks previous time-step
1919        ! Looping overall
1920        it1_tracks: DO itt=1, Ntracks(it-1)
1921          itrack = tracks(1,1,itt,it-1)
1922          ! Number polygons ID assigned
1923          Ntprev = COUNT(tracks(2,:,itt,it-1) /= 0)
1924          IF (dbg) PRINT *,itt,'  track:', itrack, 'assigned:', tracks(2,1:Ntprev,itt,it-1)
1925
1926          ! Looking for coincidencies
1927          DO iip=1, Ntprev
1928            IF (tracks(2,iip,itt,it-1) == SpolysIndep(i,it)) THEN
1929              Indeppolychained = .TRUE.
1930              IF (dbg) PRINT *,'    coincidence found by polygon:', tracks(2,iip,itt,it-1)
1931              EXIT
1932            END IF
1933          END DO
1934          IF (Indeppolychained) THEN
1935            Ntracks(it) = Ntracks(it) + 1
1936            ictrack = Ntracks(it)
1937            ! Assigning all the IDs to the next step of the track
1938            DO iip=1, NpolysIndep(i,it)
1939              iiprev = polysIndep(i,iip,it)
1940              tracks(1,iip,ictrack,it) = itrack
1941              tracks(2,iip,ictrack,it) = iiprev
1942              ixp = ctrpolys(1,iiprev,it)
1943              iyp = ctrpolys(2,iiprev,it)
1944              tracks(3,iip,ictrack,it) = ixp
1945              tracks(4,iip,ictrack,it) = iyp
1946              tracks(5,iip,ictrack,it) = it
1947            END DO
1948            EXIT
1949          END IF
1950        END DO it1_tracks
1951
1952        ! Creation of a new track
1953        IF (.NOT.Indeppolychained) THEN
1954          Ntracks(it) = Ntracks(it) + 1
1955          ictrack = Ntracks(it)
1956          ! ID of new track
1957          maxtrack = INT(MAXVAL(tracks(1,:,:,:)*1.))
1958          IF (dbg) PRINT *,'  New track!', maxtrack+1
1959
1960          ! Assigning all the IDs to the next step of the track
1961          DO j=1, NpolysIndep(i,it)
1962            iiprev = polysIndep(i,j,it)
1963            tracks(1,j,ictrack,it) = maxtrack+1
1964            tracks(2,j,ictrack,it) = iiprev
1965            ixp = ctrpolys(1,iiprev,it)
1966            iyp = ctrpolys(2,iiprev,it)
1967            tracks(3,j,ictrack,it) = ixp
1968            tracks(4,j,ictrack,it) = iyp
1969            tracks(5,j,ictrack,it) = it
1970          END DO
1971        END IF
1972
1973      END DO current_poly
1974
1975      IF (dbg) THEN
1976        PRINT *,'  At this time-step:', it, ' N trajectories:', Ntracks(it)
1977        DO i=1, Ntracks(it)
1978          Nprev = COUNT(INT(tracks(2,:,i,it)) /= 0)
1979          PRINT *,i,'tracks:', tracks(2,1:Nprev,i,it)
1980        END DO
1981      END IF
1982
1983    END DO timesteps
1984
1985    ! Summarizing trajectories
1986    ! When multiple polygons are available, the mean of their central positions determines the position
1987
1988    finaltracks = 0.
1989    maxtrack = MAXVAL(tracks(1,:,:,:))
1990
1991    DO it=1, dt
1992      DO itt=1, Ntracks(it)
1993        itrack = INT(tracks(1,1,itt,it))
1994        Nprev = COUNT(INT(tracks(2,:,itt,it)) /= 0)
1995        PRINT *,'it:', it,'itrack:', itrack, 'Nprev:', Nprev
1996        finaltracks(1,itrack,it) = itrack*1.
1997        finaltracks(2,itrack,it) = SUM(tracks(3,:,itt,it))/Nprev
1998        finaltracks(3,itrack,it) = SUM(tracks(4,:,itt,it))/Nprev
1999        finaltracks(4,itrack,it) = it*1.
2000        PRINT *,'  finaltrack:', finaltracks(:,itrack,it)
2001      END DO
2002    END DO
2003
2004    RETURN
2005
2006  END SUBROUTINE poly_overlap_tracks
2007
2008  SUBROUTINE coincidence_all_polys(dbg, dx, dy, Nallpoly, allpoly, icpolys, Npoly, polys, cpolys,     &
2009    apolys, polycoins, coinNptss)
2010! Subtourine to determine which is the coincident polygon when a boolean polygon is provided to a map of integer polygons
2011!   In case of multiple coincidencies, the closest and then the largest is taken
2012
2013    IMPLICIT NONE
2014
2015    LOGICAL, INTENT(in)                                  :: dbg
2016    INTEGER, INTENT(in)                                  :: dx, dy, Nallpoly, Npoly
2017    INTEGER, DIMENSION(dx,dy), INTENT(in)                :: allpoly, polys
2018    REAL(r_k), DIMENSION(2,Nallpoly), INTENT(in)         :: icpolys
2019    REAL(r_k), DIMENSION(2,Npoly), INTENT(in)            :: cpolys
2020    REAL(r_k), DIMENSION(Npoly), INTENT(in)              :: apolys
2021    INTEGER, DIMENSION(Nallpoly), INTENT(out)            :: polycoins
2022    INTEGER, DIMENSION(Nallpoly,Npoly), INTENT(out)      :: coinNptss
2023
2024! Local
2025    INTEGER                                              :: i, j, ip
2026    INTEGER                                              :: maxcorr
2027    INTEGER                                              :: Nmaxcorr
2028    LOGICAL, DIMENSION(dx,dy)                            :: boolpoly
2029    INTEGER                                              :: maxcoin
2030    REAL                                                 :: dist, maxcoindist, maxcoinarea
2031
2032!!!!!!! Variables
2033! dx,dy: dimension of the space
2034! Nallpoly: Number of polygons to find coincidence
2035! allpoly: space with the polygons to meet
2036! icpolys: center of the polygons to look for the coincidence
2037! Npoly: number of polygons on the 2D space
2038! polys: 2D field of polygons identified by their integer number (0 for no polygon)
2039! cpolys: center of the polygons
2040! apolys: area of the polygons
2041! polycoins: coincident polyogn
2042!          -1: no-coincidence
2043!   1 < Npoly: single coincidence with a given polygon
2044!          -9: coincidence with more than one polygon
2045! coinNptss: number of points coincident with each polygon
2046
2047    fname = 'coincidence_all_polys'
2048    IF (dbg) PRINT *,TRIM(fname)
2049
2050    DO ip=1, Nallpoly
2051      boolpoly = allpoly == ip
2052      CALL coincidence_poly(dbg, dx, dy, boolpoly, Npoly, polys, polycoins(ip), coinNptss(ip,:))
2053      IF (dbg) PRINT *,'  polygon', ip, ' coincidence with:', polycoins(ip)
2054
2055      ! Coincidence with more than one polygon
2056      IF (polycoins(ip) == -9) THEN
2057        maxcoindist = -10.
2058        maxcoinarea = -10.
2059        maxcoin = MAXVAL(coinNptss(ip,:))
2060        DO j=1, Npoly
2061          IF (coinNptss(ip,j) == maxcoin) THEN
2062            dist = SQRT( (icpolys(1,ip)*1.-cpolys(1,j)*1.)**2 + (icpolys(2,ip)*1.-cpolys(2,j)*1.)**2 )
2063            IF ( dist > maxcoindist) THEN
2064              maxcoindist = dist
2065              maxcoinarea = apolys(j)
2066              polycoins(ip) = j
2067            ELSE IF ( dist == maxcoindist) THEN
2068              IF (apolys(j) > maxcoinarea) THEN
2069                polycoins(ip) = j
2070                maxcoinarea = apolys(j)
2071              END IF
2072            END IF
2073          END IF
2074        END DO
2075      END IF
2076    END DO
2077
2078    RETURN
2079
2080  END SUBROUTINE coincidence_all_polys
2081
2082  SUBROUTINE coincidence_poly(dbg, dx, dy, poly, Npoly, polys, polycoin, coinNpts)
2083! Subtourine to determine which is the coincident polygon when a boolean polygon is provided to a map of integer polygons
2084
2085    IMPLICIT NONE
2086
2087    LOGICAL, INTENT(in)                                  :: dbg
2088    INTEGER, INTENT(in)                                  :: dx, dy, Npoly
2089    LOGICAL, DIMENSION(dx,dy), INTENT(in)                :: poly
2090    INTEGER, DIMENSION(dx,dy), INTENT(in)                :: polys
2091    INTEGER, INTENT(out)                                 :: polycoin
2092    INTEGER, DIMENSION(Npoly), INTENT(out)               :: coinNpts
2093
2094! Local
2095    INTEGER                                              :: i, j, ip
2096    INTEGER                                              :: maxcorr
2097    INTEGER                                              :: Nmaxcorr
2098
2099!!!!!!! Variables
2100! dx,dy: dimension of the space
2101! poly: bolean polygon to meet
2102! Npoly: number of polygons on the 2D space
2103! polys: 2D field of polygons identified by their integer number (0 for no polygon)
2104! polycoin: coincident polyogn
2105!          -1: no-coincidence
2106!   1 < Npoly: single coincidence with a given polygon
2107!          -9: coincidence with more than one polygon
2108! coinNpts: number of points coincident with each polygon
2109
2110    fname = 'coincidence_poly'
2111    IF (dbg) PRINT *,TRIM(fname)
2112
2113    IF (dbg) THEN
2114      PRINT *,'  Boolean polygon to search coincidences ...'
2115      DO i=1,dx
2116        PRINT *,poly(i,:)
2117      END DO
2118
2119      PRINT *,'  2D polygons space ...'
2120      DO i=1,dx
2121        PRINT '(1000(I7,1x))',polys(i,:)
2122      END DO
2123    END IF
2124
2125    ! Looking for coincient points for the polygon
2126    coinNpts = 0
2127    DO i=1,dx
2128      DO j=1,dy
2129        IF (poly(i,j) .AND. polys(i,j) .NE. 0) coinNpts(polys(i,j)) = coinNpts(polys(i,j)) + 1
2130      END DO
2131    END DO
2132
2133    maxcorr = 0
2134    maxcorr = INT(MAXVAL(coinNpts*1.))
2135
2136    IF (dbg) PRINT *,'  Maximum coincidence:', maxcorr
2137    IF (maxcorr == 0) THEN
2138      polycoin = -1
2139    ELSE
2140      Nmaxcorr = 0
2141      DO ip=1, Npoly
2142        IF (coinNpts(ip) == maxcorr) THEN
2143          Nmaxcorr=Nmaxcorr+1
2144          polycoin = ip
2145        END IF
2146      END DO
2147      IF (Nmaxcorr > 1) polycoin = -9
2148    END IF
2149
2150    IF (dbg) THEN
2151      PRINT *,'  Coincidences for each polygon _______'
2152      DO ip=1, Npoly
2153        PRINT *,'  ', ip,': ', coinNpts(ip)
2154      END DO
2155    END IF
2156
2157    RETURN
2158
2159END SUBROUTINE coincidence_poly
2160
2161  SUBROUTINE all_polygons_properties(dbg, dx, dy, Npoly, polys, lon, lat, values, xres, yres, projN,  &
2162    Npolyptss, xxtrms, yxtrms, meanctrs, meanwctrs, areas, nvals, xvals, mvals, m2vals, stdvals,      &
2163    Nquant, quants, nvcoords, xvcoords, meanvnctrs, meanvxctrs)
2164! Subroutine to determine the properties of all polygons in a 2D field:
2165!   Number of grid points
2166!   grid-point coordinates of the minimum and maximum of the path along x,y axes
2167!   grid coordinates of center from the mean of the coordinates of the poygon locations
2168!   lon, lat center from the area weighted mean of the coordinates of the polygon locations
2169!   area of the polygon (km2)
2170!   minimum and maximum of the values within the polygon
2171!   mean of the values within the polygon
2172!   quadratic mean of the values within the polygon
2173!   standard deviation of the values within the polygon
2174!   number of quantiles
2175!   quantiles of the values within the polygon
2176!   grid coordinates of the minimum, maximum value within the polygon
2177!   lon, lat coordinates of the area center weighted and also by distance to the lowest or highest values of the polygon
2178
2179  IMPLICIT NONE
2180
2181  LOGICAL, INTENT(in)                                    :: dbg
2182  INTEGER, INTENT(in)                                    :: dx, dy, Npoly, Nquant
2183  INTEGER, DIMENSION(dx,dy), INTENT(in)                  :: polys
2184  REAL(r_k), DIMENSION(dx,dy), INTENT(in)                :: lon, lat, values
2185  REAL(r_k), INTENT(in)                                  :: xres, yres
2186  CHARACTER(len=1000), INTENT(in)                        :: projN
2187  INTEGER, DIMENSION(Npoly), INTENT(out)                 :: Npolyptss
2188  INTEGER, DIMENSION(Npoly,2), INTENT(out)               :: xxtrms, yxtrms, meanctrs
2189  REAL(r_k), DIMENSION(Npoly), INTENT(out)               :: areas
2190  REAL(r_k), DIMENSION(Npoly), INTENT(out)               :: nvals, xvals, mvals, m2vals, stdvals
2191  REAL(r_k), DIMENSION(Npoly, Nquant), INTENT(out)       :: quants
2192  INTEGER, DIMENSION(Npoly,2), INTENT(out)               :: nvcoords, xvcoords
2193  REAL(r_k), DIMENSION(Npoly,2), INTENT(out)             :: meanwctrs, meanvnctrs, meanvxctrs
2194
2195! Local
2196  INTEGER                                                :: ip
2197  LOGICAL, DIMENSION(dx,dy)                              :: boolpoly
2198
2199!!!!!!! Variables
2200! dx,dy: size of the space
2201! Npoly: number of polygons
2202! polys: polygon matrix with all polygons (as integer number per polygon)
2203! lon, lat: geographical coordinates of the grid-points of the matrix
2204! values: values of the 2D field to use
2205! [x/y]res resolution along the x and y axis
2206! projN: name of the projection
2207!   'ctsarea': Constant Area
2208!   'lon/lat': for regular longitude-latitude
2209!   'nadir-sat,[lonNADIR],[latNADIR]': for satellite data with the resolution given at nadir (lonNADIR, latNADIR)
2210! Npolyptss: number of points of the polygons
2211! [x/y]xtrms: grid-point coordinates of minimum and maximum coordinates of the polygons
2212! meanctrs: center from the mean of the coordinates of the polygons
2213! meanwctrs: lon, lat coordinates of the center from the spatial-weighted mean of the polygons
2214! areas: area of the polygons [km]
2215! [n/x]vals: minimum and maximum of the values within the polygons
2216! mvals: mean of the values within the polygons
2217! m2vals: quadratic mean of the values within the polygons
2218! stdvals: standard deviation of the values within the polygons
2219! Nquant: number of quantiles
2220! quants: quantiles of the values within the polygons
2221! [n/x]vcoords: grid coordinates of the minimum/maximum of the values within the polygons
2222! meanv[n/x]ctrs: lon, lat coordinates of the area center weighted and also by distance to the lowest or highest values of the polygons
2223
2224  fname = 'all_polygons_properties'
2225
2226  ! Initializing matrices
2227  Npolyptss = -1
2228  xxtrms = fillval64
2229  yxtrms = fillval64
2230  meanctrs = fillval64
2231  meanwctrs = fillval64
2232  areas = fillval64
2233  nvals = fillvalI
2234  xvals = fillval64
2235  mvals = fillval64
2236  m2vals = fillval64
2237  stdvals = fillval64
2238  quants = fillval64
2239  nvcoords = fillvalI
2240  xvcoords = fillvalI
2241  meanvnctrs = fillval64
2242  meanvxctrs = fillval64
2243
2244  DO ip=1, Npoly
2245    boolpoly = polys == ip
2246    CALL polygon_properties(dbg, dx, dy, boolpoly, lon, lat, values, xres, yres, projN, Npolyptss(ip),&
2247      xxtrms(ip,:), yxtrms(ip,:), meanctrs(ip,:), meanwctrs(ip,:), areas(ip), nvals(ip), xvals(ip),   &
2248      mvals(ip), m2vals(ip), stdvals(ip), Nquant, quants(ip,:), nvcoords(ip,:), xvcoords(ip,:),       &
2249      meanvnctrs(ip,:), meanvxctrs(ip,:))
2250  END DO
2251
2252  RETURN
2253
2254  END SUBROUTINE all_polygons_properties
2255
2256  SUBROUTINE polygon_properties(dbg, dx, dy, poly, lon, lat, values, xres, yres, projN, Npolypts,     &
2257    xxtrm, yxtrm, meanctr, meanwctr, area, nval, xval, mval, m2val, stdval, Nquant, quant, nvcoord,   &
2258    xvcoord, meanvnctr, meanvxctr)
2259! Subroutine to determine the properties of a polygon (as .TRUE. matrix)
2260!   Number of grid points
2261!   grid-point coordinates of the minimum and maximum of the path along x,y axes
2262!   grid coordinates of center from the mean of the coordinates of the poygon locations
2263!   lon, lat center from the area weighted mean of the coordinates of the polygon locations
2264!   area of the polygon (km2)
2265!   minimum and maximum of the values within the polygon
2266!   mean of the values within the polygon
2267!   quadratic mean of the values within the polygon
2268!   standard deviation of the values within the polygon
2269!   number of quantiles
2270!   quantiles of the values within the polygon
2271!   grid coordinates of the minimum, maximum value within the polygon
2272!   lon, lat coordinates of the area center weighted and also by distance to the lowest or highest values of the polygon
2273
2274  IMPLICIT NONE
2275
2276  LOGICAL, INTENT(in)                                    :: dbg
2277  INTEGER, INTENT(in)                                    :: dx, dy, Nquant
2278  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: poly
2279  REAL(r_k), DIMENSION(dx,dy), INTENT(in)                :: lon, lat, values
2280  REAL(r_k), INTENT(in)                                  :: xres, yres
2281  CHARACTER(len=1000), INTENT(in)                        :: projN
2282  INTEGER, INTENT(out)                                   :: Npolypts
2283  INTEGER, DIMENSION(2), INTENT(out)                     :: xxtrm, yxtrm, meanctr
2284  INTEGER, DIMENSION(2), INTENT(out)                     :: nvcoord, xvcoord
2285  REAL(r_k), DIMENSION(2), INTENT(out)                   :: meanwctr, meanvnctr, meanvxctr
2286  REAL(r_k), INTENT(out)                                 :: area
2287  REAL(r_k), INTENT(out)                                 :: nval, xval, mval, m2val, stdval
2288  REAL(r_k), DIMENSION(Nquant), INTENT(out)              :: quant
2289
2290! Local
2291  INTEGER                                                :: i, j, ip
2292  INTEGER                                                :: ierr
2293  INTEGER, DIMENSION(:,:), ALLOCATABLE                   :: polypts
2294  REAL(r_k), DIMENSION(:), ALLOCATABLE                   :: polyvals, distvn, distvx
2295  REAL(r_k)                                              :: lonNADIR, latNADIR
2296  REAL(r_k)                                              :: sumRESx, sumRESy
2297  REAL(r_k), DIMENSION(dx,dy)                            :: xcorr, ycorr
2298  CHARACTER(len=200), DIMENSION(3)                       :: satSvals
2299  CHARACTER(len=50)                                      :: projS
2300  REAL(r_k)                                              :: sumDISTnlon, sumDISTnlat, sumDISTxlon,   &
2301    sumDISTxlat
2302
2303!!!!!!! Variables
2304! dx,dy: size of the space
2305! poly: polygon matrix (boolean)
2306! lon, lat: geographical coordinates of the grid-points of the matrix
2307! values: values of the 2D field to use
2308! [x/y]res resolution along the x and y axis
2309! projN: name of the projection
2310!   'ctsarea': Constant Area
2311!   'lon/lat': for regular longitude-latitude
2312!   'nadir-sat,[lonNADIR],[latNADIR]': for satellite data with the resolution given at nadir (lonNADIR, latNADIR)
2313! Npolypts: number of points of the polygon
2314! [x/y]xtrm: grid-point coordinates of minimum and maximum coordinates of the polygon
2315! meanctr: center from the mean of the coordinates of the polygon
2316! meanwctr: lon, lat coordinates of the center from the spatial-weighted mean of the polygon
2317! area: area of the polygon [km]
2318! [n/x]val: minimum and maximum of the values within the polygon
2319! mval: mean of the values within the polygon
2320! m2val: quadratic mean of the values within the polygon
2321! stdval: standard deviation of the values within the polygon
2322! Nquant: number of quantiles
2323! quant: quantiles of the values within the polygon
2324! [n/x]vcoord: grid coordinates of the minimum/maximum of the values within the polygon
2325! meanv[n/x]ctr: lon, lat coordinates of the area center weighted and also by distance to the lowest or highest values of the polygon
2326
2327  fname = 'polygon_properties'
2328
2329  IF (dbg) PRINT *,"  '" // TRIM(fname) // "' ..."
2330
2331  ! Getting grid-point coordinates of the polygon
2332  Npolypts = COUNT(poly)
2333
2334  IF (ALLOCATED(polypts)) DEALLOCATE(polypts)
2335  ALLOCATE(polypts(Npolypts,2), STAT=ierr)
2336  msg = "Problems allocating 'polypts'"
2337  CALL ErrMsg(msg, fname, ierr)
2338
2339  IF (ALLOCATED(polyvals)) DEALLOCATE(polyvals)
2340  ALLOCATE(polyvals(Npolypts), STAT=ierr)
2341  msg = "Problems allocating 'polyvals'"
2342  CALL ErrMsg(msg, fname, ierr)
2343
2344  IF (ALLOCATED(distvn)) DEALLOCATE(distvn)
2345  ALLOCATE(distvn(Npolypts), STAT=ierr)
2346  msg = "Problems allocating 'distvn'"
2347  CALL ErrMsg(msg, fname, ierr)
2348
2349  IF (ALLOCATED(distvx)) DEALLOCATE(distvx)
2350  ALLOCATE(distvx(Npolypts), STAT=ierr)
2351  msg = "Problems allocating 'distvx'"
2352  CALL ErrMsg(msg, fname, ierr)
2353
2354  IF (projN(1:7) == 'lon/lat') THEN
2355    projS = projN
2356  ELSE IF (projN(1:7) == 'ctsarea') THEN
2357    projS = projN
2358  ELSE IF (projN(1:9) == 'nadir-sat') THEN
2359    projS = 'nadir-sat'
2360    CALL split(projN, ',', 3, satSvals)
2361    READ(satSvals(2),'(F200.100)')lonNadir
2362    READ(satSvals(3),'(F200.100)')latNadir
2363    IF (dbg) PRINT *,"  'nadir-geostationary-satellite' based projection of data with nadir " //      &
2364      "location at:", lonNadir, latNadir
2365  ELSE
2366    msg = "Projection '" // TRIM(projN) // "' not ready" // CHAR(10) // " available ones: " //        &
2367       "'ctsarea', 'lon/lat', 'nadir-sat'"
2368    CALL ErrMsg(msg,fname,-1)
2369  END IF
2370
2371  area = 0.
2372  sumRESx = 0.
2373  sumRESy = 0.
2374  meanwctr = 0.
2375  meanvnctr = 0.
2376  meanvxctr = 0.
2377  xcorr = 0.
2378  ycorr = 0.
2379
2380  nval = fillval64
2381  xval = -fillval64
2382
2383  ip = 1
2384  DO i=1,dx
2385    DO j=1,dy
2386      IF (poly(i,j)) THEN
2387        polypts(ip,1) = i
2388        polypts(ip,2) = j
2389        polyvals(ip) = values(i,j)
2390        SELECT CASE (TRIM(projS))
2391          CASE ('ctsarea')
2392            ! Constant Area
2393            xcorr(i,j) = 1.
2394            ycorr(i,j) = 1.
2395          CASE ('lon/lat')
2396            ! Area as fixed yres and sinus-lat varying for xres
2397!            IF (KIND(xcorr(i,j)) == KIND(1.d0)) THEN
2398!              xcorr(i,j) = DABS(DSIN(lon(i,j)*DegRad))
2399!            ELSE
2400              xcorr(i,j) = ABS(SIN(lon(i,j)*DegRad))
2401!            END IF
2402            ycorr(i,j) = 1.
2403          CASE ('nadir-sat')
2404            ! Area from nadir resolution and degrading as we get far from satellite's nadir
2405            ! GOES-E: 0 N, 75 W
2406!            IF (KIND(xcorr(i,j)) == KIND(1.d0)) THEN
2407!              xcorr(i,j) = DABS(DSIN(lon(i,j)*DegRad))
2408!            ELSE
2409              xcorr(i,j) = ABS(SIN(lon(i,j)*DegRad))
2410!            END IF
2411            ycorr(i,j) = 1.
2412        END SELECT
2413        area = area + xres*xcorr(i,j)*yres*ycorr(i,j)
2414        meanwctr(1) = meanwctr(1) + lon(i,j)*xres*xcorr(i,j)
2415        meanwctr(2) = meanwctr(2) + lat(i,j)*yres*ycorr(i,j)
2416        IF (nval > values(i,j)) THEN
2417          nvcoord(1) = i
2418          nvcoord(2) = j
2419          nval = values(i,j)
2420        END IF
2421        IF (xval < values(i,j)) THEN
2422          xvcoord(1) = i
2423          xvcoord(2) = j
2424          xval = values(i,j)
2425        END IF
2426        ip = ip + 1
2427      END IF
2428    END DO
2429  END DO
2430
2431  IF (dbg) THEN
2432    PRINT *,'  grid_coord lon lat value _______ '
2433    DO ip=1, Npolypts
2434      PRINT *, polypts(ip,:), ';', lon(polypts(ip,1),polypts(ip,2)), lat(polypts(ip,1),polypts(ip,2)),&
2435         ':', polyvals(ip)
2436    END DO
2437  END IF
2438
2439  sumRESx = xres*SUM(xcorr)
2440  sumRESy = yres*SUM(ycorr)
2441
2442  xxtrm = (/ MINVAL(polypts(:,1)), MAXVAL(polypts(:,1)) /)
2443  yxtrm = (/ MINVAL(polypts(:,2)), MAXVAL(polypts(:,2)) /)
2444  meanctr = (/ SUM(polypts(:,1))/Npolypts, SUM(polypts(:,2))/Npolypts /)
2445  meanwctr = (/ meanwctr(1)/sumRESx, meanwctr(2)/sumRESy /)
2446
2447  IF (dbg) THEN
2448    PRINT *,'  mean grid center: ', meanctr, ' weighted mean center: ', meanwctr
2449  END IF
2450
2451  ! Statistics of the values within the polygon
2452  CALL StatsR_K(Npolypts, polyvals, nval, xval, mval, m2val, stdval)
2453
2454  IF (dbg) THEN
2455    PRINT *,'    minimum value: ', nval, ' maximum:', xval, ' mean:', mval
2456    PRINT *,'    coor. minimum: ', nvcoord
2457    PRINT *,'    coor. maximum: ', xvcoord
2458  END IF
2459
2460  ! Mean center weighted to minimum and maximum values
2461!  IF (KIND(polyvals(1)) == KIND(1.d0)) THEN
2462!    distvn = DABS(polyvals - nval)
2463!    distvx = DABS(polyvals - xval)
2464!  ELSE
2465    distvn = ABS(polyvals - nval)
2466    distvx = ABS(polyvals - xval)
2467!  END IF
2468
2469  meanvnctr = 0.
2470  meanvxctr = 0.
2471  sumDISTnlon = 0.
2472  sumDISTnlat = 0.
2473  sumDISTxlon = 0.
2474  sumDISTxlat = 0.
2475
2476  ip = 1
2477  DO i=1,dx
2478    DO j=1,dy
2479      IF (poly(i,j)) THEN
2480        meanvnctr(1) = meanvnctr(1)+lon(i,j)*distvn(ip)*xres*xcorr(i,j)
2481        meanvnctr(2) = meanvnctr(2)+lat(i,j)*distvn(ip)*yres*ycorr(i,j)
2482
2483        meanvxctr(1) = meanvxctr(1)+lon(i,j)*distvx(ip)*xres*xcorr(i,j)     
2484        meanvxctr(2) = meanvxctr(2)+lat(i,j)*distvx(ip)*yres*ycorr(i,j)
2485
2486        sumDISTnlon = sumDISTnlon + distvn(ip)*xres*xcorr(i,j)
2487        sumDISTnlat = sumDISTnlat + distvn(ip)*yres*ycorr(i,j)
2488        sumDISTxlon = sumDISTxlon + distvx(ip)*xres*xcorr(i,j)
2489        sumDISTxlat = sumDISTxlat + distvx(ip)*yres*ycorr(i,j)
2490
2491        ip = ip + 1
2492      END IF
2493    END DO
2494  END DO
2495
2496  meanvnctr = (/ meanvnctr(1)/sumDISTnlon, meanvnctr(2)/sumDISTnlat /)
2497  meanvxctr = (/ meanvxctr(1)/sumDISTxlon, meanvxctr(2)/sumDISTxlat /)
2498
2499  IF (dbg) THEN
2500    PRINT *,'  mean center to minimum: ', meanvnctr, ' to maximum: ', meanvxctr
2501  END IF
2502
2503  ! Quantiles of the values within the polygon
2504  quant = -9999.d0
2505  IF (Npolypts > Nquant) THEN
2506    CALL quantilesR_K(Npolypts, polyvals, Nquant, quant)
2507  ELSE
2508    CALL SortR_K(polyvals, Npolypts)
2509  END IF
2510
2511  DEALLOCATE (polypts)
2512  DEALLOCATE (polyvals)
2513
2514  RETURN
2515
2516  END SUBROUTINE polygon_properties
2517
2518SUBROUTINE polygons_t(dbg, dx, dy, dt, boolmatt, polys, Npoly)
2519! Subroutine to search the polygons of a temporal series of boolean fields. FORTRAN based. 1st = 1!
2520
2521  IMPLICIT NONE
2522
2523  INTEGER, INTENT(in)                                    :: dx, dy, dt
2524  LOGICAL, DIMENSION(dx,dy,dt), INTENT(in)               :: boolmatt
2525  LOGICAL, INTENT(in)                                    :: dbg
2526  INTEGER, DIMENSION(dt), INTENT(out)                    :: Npoly
2527  INTEGER, DIMENSION(dx,dy,dt), INTENT(out)              :: polys
2528
2529! Local
2530  INTEGER                                                :: i,it
2531
2532!!!!!!! Variables
2533! dx,dy: spatial dimensions of the space
2534! boolmatt: boolean matrix tolook for the polygons (.TRUE. based)
2535! polys: found polygons
2536! Npoly: number of polygons found
2537
2538  fname = 'polygons'
2539
2540  IF (dbg) PRINT *,TRIM(fname)
2541
2542  polys = -1
2543  Npoly = 0
2544
2545  DO it=1,dt
2546    IF (ANY(boolmatt(:,:,it))) THEN
2547      IF (dbg) THEN
2548        PRINT *,'  it:', it, ' num. TRUE:', COUNT(boolmatt(:,:,it)), 'bool _______'
2549        DO i=1,dx
2550          PRINT *,boolmatt(i,:,it)
2551        END DO
2552      END IF
2553      CALL polygons(dbg, dx, dy, boolmatt(:,:,it), polys(:,:,it), Npoly(it))
2554    ELSE
2555      IF (dbg) THEN
2556        PRINT *,'  it:', it, " without '.TRUE.' values skipiing it!!"
2557      END IF
2558    END IF
2559  END DO
2560
2561END SUBROUTINE polygons_t
2562
2563SUBROUTINE polygons(dbg, dx, dy, boolmat, polys, Npoly)
2564! Subroutine to search the polygons of a boolean field. FORTRAN based. 1st = 1!
2565
2566  IMPLICIT NONE
2567
2568  INTEGER, INTENT(in)                                    :: dx, dy
2569  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: boolmat
2570  LOGICAL, INTENT(in)                                    :: dbg
2571  INTEGER, INTENT(out)                                   :: Npoly
2572  INTEGER, DIMENSION(dx,dy), INTENT(out)                 :: polys
2573
2574! Local
2575  INTEGER                                                :: i, j, k, ip, ipp, Nppt
2576  INTEGER                                                :: ierr
2577  INTEGER, DIMENSION(:,:), ALLOCATABLE                   :: borders
2578  LOGICAL, DIMENSION(dx,dy)                              :: isborder, isbordery, borderp
2579  INTEGER, DIMENSION(:,:,:), ALLOCATABLE                 :: paths
2580  INTEGER                                                :: Npath
2581  INTEGER, DIMENSION(:), ALLOCATABLE                     :: Nptpaths
2582  INTEGER, DIMENSION(2)                                  :: xtrx, xtry, meanpth
2583  INTEGER                                                :: Nvertx, Npts
2584  INTEGER, DIMENSION(:,:), ALLOCATABLE                   :: vertxs, points
2585  LOGICAL, DIMENSION(:), ALLOCATABLE                     :: isin
2586  CHARACTER(len=1000)                                    :: boundsS
2587
2588!!!!!!! Variables
2589! dx,dy: spatial dimensions of the space
2590! boolmat: boolean matrix tolook for the polygons (.TRUE. based)
2591! polys: found polygons
2592! Npoly: number of polygons found
2593
2594  fname = 'polygons'
2595
2596  polys = -1
2597
2598  ! The mathematical maximum woiuld be dx*dy/4, but let's be optimistic... (sorry Jero)
2599  Nppt = dx*dy/100
2600
2601  IF (ALLOCATED(borders)) DEALLOCATE(borders)
2602  ALLOCATE(borders(Nppt,2), STAT=ierr)
2603  msg = "Problems allocating matrix 'borders'"
2604  CALL ErrMsg(msg, fname, ierr)
2605
2606  IF (ALLOCATED(paths)) DEALLOCATE(paths)
2607  ALLOCATE(paths(Nppt,Nppt,2), STAT=ierr)
2608  boundsS = vectorI_S(3, (/Nppt, Nppt, 2/))
2609  msg = "Problems allocating matrix 'paths' shape: " // TRIM(boundsS) // " try to reduce Nppt " //    &
2610    "and recompile"
2611  CALL ErrMsg(msg, fname, ierr)
2612
2613  IF (ALLOCATED(Nptpaths)) DEALLOCATE(Nptpaths)
2614  ALLOCATE(Nptpaths(Nppt), STAT=ierr)
2615  msg = "Problems allocating matrix 'Nptpaths'"
2616  CALL ErrMsg(msg, fname, ierr)
2617
2618  ! Filling with the points of all the space with .TRUE.
2619  Npts = COUNT(boolmat)
2620  PRINT *, dx, dy, 'Lluis Npts:', Npts, 'Nppt:', Nppt
2621
2622  IF (ALLOCATED(points)) DEALLOCATE(points)
2623  ALLOCATE(points(dy,2), STAT=ierr)
2624  msg = "Problems allocating matrix 'points'"
2625  CALL ErrMsg(msg, fname, ierr)
2626
2627  CALL borders_matrixL(dbg, dx, dy, Nppt, boolmat, borders, isborder, isbordery)
2628  CALL paths_border(dbg, dx, dy, isborder, Nppt, borders, paths, Npath, Nptpaths)
2629
2630  Npoly = Npath
2631
2632  DO ip=1, Npath
2633    IF (ALLOCATED(vertxs)) DEALLOCATE(vertxs)
2634    ALLOCATE(vertxs(Nptpaths(ip),2))
2635    msg = "Problems allocating matrix 'vertxs'"
2636    CALL ErrMsg(msg, fname, ierr)
2637
2638    IF (ALLOCATED(isin)) DEALLOCATE(isin)
2639    ALLOCATE(isin(Npts), STAT=ierr)
2640    msg = "Problems allocating matrix 'isin'"
2641    CALL ErrMsg(msg, fname, ierr)
2642
2643    isin = .FALSE.
2644
2645    borderp = .FALSE.
2646    DO j=1,Nptpaths(ip)
2647      borderp(paths(ip,j,1),paths(ip,j,2)) = .TRUE.
2648    END DO
2649
2650    CALL path_properties(dx, dy, boolmat, Nptpaths(ip), paths(ip,1:Nptpaths(ip),:), xtrx, xtry,       &
2651      meanpth, 'y', Nvertx, vertxs)
2652
2653    IF (dbg) THEN
2654      PRINT *, '    properties  _______'
2655      PRINT *, '    x-extremes:', xtrx
2656      PRINT *, '    y-extremes:', xtry
2657      PRINT *, '    center mean:', meanpth
2658      PRINT *, '    y-vertexs:', Nvertx,' ________'
2659      DO i=1, Nvertx
2660        PRINT *,'      ',i,':',vertxs(i,:)
2661      END DO
2662    END IF
2663 
2664!    CALL gridpoints_InsidePolygon(dbg, dx, dy, isbordery, Nptpaths(ip), paths(ip,1:Nptpaths(ip),:),   &
2665!      Nvertx, xtrx, xtry, vertxs, Npts, points, isin)
2666
2667    ! We only want to localize that points 'inside'
2668    Npts = 1
2669    DO i=xtrx(1), xtrx(2)
2670      DO j=1, dy
2671        IF (boolmat(i,j)) THEN
2672          points(Npts,1) = i
2673          points(Npts,2) = j
2674          Npts = Npts + 1
2675        END IF
2676      END DO
2677      CALL gridpoints_InsidePolygon_ray(dbg,dy,borderp(i,:), Nptpaths(ip), paths(ip,1:Nptpaths(ip),:),&
2678        Nvertx, xtrx, xtry, vertxs, Npts, points, isin)
2679
2680      ! Filling polygons
2681      DO ipp=1, Npts
2682        IF (isin(ipp)) polys(points(ipp,1),points(ipp,2)) = ip
2683      END DO
2684
2685      IF (dbg) THEN
2686        PRINT *,'  path boolmat isborder isborderp polygon (', xtrx(1), ',', xtry(1), ')x(', xtrx(2), &
2687          ',', xtry(2), ') _______' , Npts
2688        PRINT *,ip,'<>', i,':',boolmat(i,xtry(1):xtry(2)), ' border ', isborder(i,xtry(1):xtry(2)),   &
2689          ' isbordery ', borderp(i,xtry(1):xtry(2)), ' polygon ', polys(i,xtry(1):xtry(2))
2690      END IF
2691
2692    END DO
2693  END DO
2694  PRINT *,'  PRE-clean '
2695
2696  ! Cleaning polygons matrix of not-used and paths around holes
2697  !CALL clean_polygons(dx, dy, boolmat, polys, Npoly, dbg)
2698
2699  IF (ALLOCATED(borders)) DEALLOCATE (borders)
2700  IF (ALLOCATED(Nptpaths)) DEALLOCATE (Nptpaths)
2701  IF (ALLOCATED(paths)) DEALLOCATE (paths)
2702  IF (ALLOCATED(vertxs)) DEALLOCATE (vertxs)
2703  IF (ALLOCATED(points)) DEALLOCATE (points)
2704  IF (ALLOCATED(isin)) DEALLOCATE (isin)
2705
2706  RETURN
2707
2708END SUBROUTINE polygons
2709
2710SUBROUTINE clean_polygons(dx, dy, Lmat, pols, Npols, dbg)
2711! Subroutine to clean polygons from non-used paths, polygons only left as path since they are inner path of a hole
2712
2713  IMPLICIT NONE
2714
2715  INTEGER, INTENT(in)                                    :: dx, dy
2716  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: Lmat
2717  INTEGER, INTENT(inout)                                 :: Npols
2718  INTEGER, DIMENSION(dx,dy), INTENT(inout)               :: pols
2719  LOGICAL, INTENT(in)                                    :: dbg
2720
2721! Local
2722  INTEGER                                                :: i,j,ip,iprm
2723  INTEGER, DIMENSION(Npols)                              :: origPol, NotPol, neigPol
2724  INTEGER                                                :: ispol, NnotPol
2725  CHARACTER(len=4)                                       :: ISa
2726
2727!!!!!!! Variables
2728! dx, dy: size of the space
2729! Lmat: original bolean matrix from which the polygons come from
2730! Npols: original number of polygons
2731! pols: polygons space
2732
2733  fname = 'clean_polygons'
2734  IF (dbg) PRINT *,"  At '" // TRIM(fname) // "' ..."
2735
2736  origPol = -1
2737
2738  ! Looking for polygons already in space
2739  NnotPol = 0
2740  DO ip=1, Npols
2741    ispol = COUNT(pols-ip == 0)
2742    IF (ispol > 0) THEN
2743      origPol(ip) = ip
2744    ELSE
2745      NnotPol = NnotPol + 1
2746      NotPol(NnotPol) = ip
2747      neigPol(NnotPol) = -1
2748    END IF
2749  END DO
2750
2751  IF (NnotPol == Npols) THEN
2752    PRINT *,'  ' // TRIM(fname) // ": avoiding to remove all polygons !!"
2753    NnotPol = 0
2754  END IF
2755
2756  IF (dbg) THEN
2757    PRINT *,'  It should be:', Npols, ' polygons, but already there are:', Npols - NnotPol
2758    PRINT *,'  Polygons to remove:', NotPol(1:NnotPol)
2759  END IF
2760 
2761  ! Looking for the hole border of a polygon. This is identify as such polygon point which along
2762  !   y-axis has NpolygonA, Npolygon, .FALSE.
2763  DO i=1,dx
2764    DO j=2,dy-1
2765      IF  ( (pols(i,j-1) /= pols(i,j) .AND. pols(i,j+1) == -1) .AND. (COUNT(NotPol-pols(i,j)==0)==0)  &
2766        .AND. (pols(i,j) /= -1) .AND. (pols(i,j-1) /= -1)) THEN
2767        IF (dbg) PRINT *,'  Polygon:', pols(i,j), ' to be removed at point (',i,',',j,'); j-1:',      &
2768          pols(i,j-1), ' j:', pols(i,j), ' j+1:', pols(i,j+1)
2769        NnotPol = NnotPol + 1
2770        NotPol(NnotPol) = pols(i,j)
2771        neigPol(NnotPol) = pols(i,j-1)
2772      END IF
2773    END DO
2774  END DO
2775
2776  IF (dbg) THEN
2777    PRINT *,'  It should be:', Npols, ' polygons, but already there are:', Npols - NnotPol
2778    PRINT *,'  Polygons to remove after looking for fake border-of-hole polygons _______'
2779    DO i=1, NnotPol
2780      PRINT *, '      Polygon:', NotPol(i), ' to be replaced by:', neigPol(i)
2781    END DO
2782  END IF
2783
2784  ! Removing polygons
2785  DO iprm=1, NnotPol
2786    IF (neigPol(iprm) == -1) THEN
2787      WHERE (pols == NotPol(iprm))
2788        pols = -1
2789      END WHERE
2790      IF (dbg) THEN
2791        PRINT *,'    removing polygon:', NotPol(iprm)
2792      END IF
2793    ELSE
2794      WHERE (pols == NotPol(iprm))
2795        pols = neigPol(iprm)
2796      END WHERE
2797      IF (dbg) THEN
2798        PRINT *,'       replacing polygon:', NotPol(iprm), ' by:', neigPol(iprm)
2799      END IF
2800    END IF
2801  END DO
2802
2803  ! Re-numbering (descending values)
2804  DO i = 1, NnotPol
2805    iprm = MAXVAL(NotPol(1:NnotPol))
2806    WHERE(pols > iprm)
2807      pols = pols - 1
2808    END WHERE
2809    j = Index1DArrayI(NotPol, NnotPol, iprm)
2810    NotPol(j) = -9
2811  END DO
2812
2813  Npols = Npols - NnotPol
2814
2815  RETURN
2816
2817END SUBROUTINE clean_polygons
2818
2819  SUBROUTINE path_properties(dx, dy, Lmat, Nptspth, pth, xxtrm, yxtrm, meanctr, axs, Nvrtx, vrtxs)
2820! Subroutine to determine the properties of a path:
2821!   extremes: minimum and maximum of the path along x,y axes
2822!   meancenter: center from the mean of the coordinates of the paths locations
2823!   vertexs: path point, without neighbours along a given axis
2824
2825  IMPLICIT NONE
2826
2827  INTEGER, INTENT(in)                                    :: dx, dy, Nptspth
2828  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: Lmat
2829  INTEGER, DIMENSION(Nptspth,2), INTENT(in)              :: pth
2830  CHARACTER, INTENT(in)                                  :: axs
2831  INTEGER, DIMENSION(2), INTENT(out)                     :: meanctr, xxtrm, yxtrm
2832  INTEGER, INTENT(out)                                   :: Nvrtx
2833  INTEGER, DIMENSION(Nptspth,2), INTENT(out)             :: vrtxs
2834
2835! Local
2836  INTEGER                                                :: i, ip, jp
2837  INTEGER                                                :: neig1, neig2
2838
2839!!!!!!! Variables
2840! dx,dy: size of the space
2841! Lmat: original matrix of logical values for the path
2842! Nptspth: number of points of the path
2843! pth: path coordinates (clockwise)
2844! axs: axis of finding the vertex
2845! [x/y]xtrm: minimum and maximum coordinates of the path
2846! meanctr: center from the mean of the coordinates of the path
2847! Nvrtx: Number of vertexs of the path
2848! vrtxs: coordinates of the vertexs
2849
2850  fname = 'path_properties'
2851
2852  vrtxs = -1
2853  Nvrtx = 0
2854
2855  xxtrm = (/ MINVAL(pth(:,1)), MAXVAL(pth(:,1)) /)
2856  yxtrm = (/ MINVAL(pth(:,2)), MAXVAL(pth(:,2)) /)
2857  meanctr = (/ SUM(pth(:,1))/Nptspth, SUM(pth(:,2))/Nptspth /)
2858
2859  IF (axs == 'x' .OR. axs == 'X') THEN
2860    ! Looking vertexs along x-axis
2861    DO i=1, Nptspth
2862      ip = pth(i,1)
2863      jp = pth(i,2)
2864      neig1 = 0
2865      neig2 = 0
2866      ! W-point
2867      IF (ip == 1) THEN
2868        neig1 = -1
2869      ELSE
2870        IF (.NOT.Lmat(ip-1,jp)) neig1 = -1
2871      END IF
2872      ! E-point
2873      IF (ip == dx) THEN
2874        neig2 = -1
2875      ELSE
2876        IF (.NOT.Lmat(ip+1,jp)) neig2 = -1
2877      END IF
2878   
2879      IF (neig1 == -1 .AND. neig2 == -1) THEN
2880        Nvrtx = Nvrtx + 1
2881        vrtxs(Nvrtx,:) = (/ip,jp/)
2882      END IF
2883    END DO
2884  ELSE IF (axs == 'y' .OR. axs == 'Y') THEN
2885    ! Looking vertexs along x-axis
2886    DO i=1, Nptspth
2887      ip = pth(i,1)
2888      jp = pth(i,2)
2889
2890      neig1 = 0
2891      neig2 = 0
2892      ! S-point
2893      IF (jp == 1) THEN
2894        neig1 = -1
2895      ELSE
2896        IF (.NOT.Lmat(ip,jp-1)) neig1 = -1
2897      END IF
2898      ! N-point
2899      IF (jp == dy) THEN
2900        neig2 = -1
2901      ELSE
2902        IF (.NOT.Lmat(ip,jp+1)) neig2 = -1
2903      END IF
2904
2905      IF (neig1 == -1 .AND. neig2 == -1) THEN
2906        Nvrtx = Nvrtx + 1
2907        vrtxs(Nvrtx,:) = (/ ip, jp /)
2908      END IF
2909    END DO
2910  ELSE
2911    msg = "Axis '" // axs // "' not available" // CHAR(10) // "  Available ones: 'x', 'X', 'y, 'Y'"
2912    CALL ErrMsg(msg, fname, -1)
2913  END IF
2914
2915  RETURN
2916
2917  END SUBROUTINE path_properties
2918
2919  SUBROUTINE gridpoints_InsidePolygon(dbg, dx, dy, isbrdr, Npath, path, Nvrtx, xpathxtrm, ypathxtrm,  &
2920    vrtxs, Npts, pts, inside)
2921! Subroutine to determine if a series of grid points are inside a polygon following ray casting algorithm
2922! FROM: https://en.wikipedia.org/wiki/Point_in_polygon
2923
2924  IMPLICIT NONE
2925
2926  INTEGER, INTENT(in)                                    :: dx,dy,Npath,Nvrtx,Npts
2927  LOGICAL, INTENT(in)                                    :: dbg
2928  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: isbrdr
2929  INTEGER, DIMENSION(Npath,2), INTENT(in)                :: path
2930  INTEGER, DIMENSION(2), INTENT(in)                      :: xpathxtrm, ypathxtrm
2931  INTEGER, DIMENSION(Npath,2)                            :: vrtxs
2932  INTEGER, DIMENSION(Npts,2), INTENT(in)                 :: pts
2933  LOGICAL, DIMENSION(Npts), INTENT(out)                  :: inside
2934
2935! Local
2936  INTEGER                                                :: i,j,ip,ix,iy
2937  INTEGER                                                :: Nintersecs, isvertex, ispath
2938  INTEGER                                                :: ierr
2939  LOGICAL, DIMENSION(:,:), ALLOCATABLE                   :: halo_brdr
2940  INTEGER                                                :: Nbrbrdr
2941
2942!!!!!!! Variables
2943! dx,dy: space size
2944! Npath: number of points of the path of the polygon
2945! path: path of the polygon
2946! isbrdr: boolean matrix of the space wqith .T. on polygon border
2947! Nvrtx: number of vertexs of the path
2948! [x/y]pathxtrm extremes of the path
2949! vrtxs: vertexs of the path along y-axis
2950! Npts: number of points
2951! pts: points to look for
2952! inside: vector wether point is inside or not (coincident to a border is inside)
2953
2954  fname = 'gridpoints_InsidePolygon'
2955
2956  ! Creation of a 1-grid point larger matrix to deal with points reaching the limits
2957  IF (ALLOCATED(halo_brdr)) DEALLOCATE(halo_brdr)
2958  ALLOCATE(halo_brdr(dx+2,dy+2), STAT=ierr)
2959  msg = "Problems allocating matrix 'halo_brdr'"
2960  CALL ErrMsg(msg, fname, ierr)
2961  halo_brdr = .FALSE.
2962
2963  IF (dbg) PRINT *,'Border _______'
2964  DO i=1,dx
2965    halo_brdr(i+1,2:dy+1) = isbrdr(i,:)
2966    IF (dbg) PRINT *,isbrdr(i,:)
2967  END DO
2968
2969  inside = .FALSE.
2970
2971  DO ip=1,Npts
2972    Nintersecs = 0
2973    ix = pts(ip,1)
2974    iy = pts(ip,2)
2975    ! Point might be outside path range...
2976    IF (ix >= xpathxtrm(1) .AND. ix <= xpathxtrm(2) .AND. iy >= ypathxtrm(1) .AND.                    &
2977      iy <= ypathxtrm(2)) THEN
2978
2979      ! It is a border point?
2980      ispath = index_list_coordsI(Npath, path, (/ix,iy/))
2981      IF (isbrdr(ix,iy) .AND. (ispath /= -1)) THEN
2982        inside(ip) = .TRUE.
2983        CYCLE
2984      END IF
2985
2986      ! Looking along y-axis
2987      ! Accounting for consecutives borders
2988      Nbrbrdr = 0
2989      DO j=MAX(1,ypathxtrm(1)-1),iy-1
2990        ! Only counting that borders that are not vertexs
2991        ispath = index_list_coordsI(Npath, path, (/ix,j/))
2992        isvertex = index_list_coordsI(Npath, vrtxs, (/ix,j/))
2993
2994        IF (halo_brdr(ix+1,j+1) .AND. (ispath /= -1) .AND. (isvertex == -1) ) Nintersecs = Nintersecs + 1
2995        IF (halo_brdr(ix+1,j+1) .AND. (ispath /= -1) .AND. (halo_brdr(ix+1,j+1) .EQV. halo_brdr(ix+1,j+2))) THEN
2996          Nbrbrdr = Nbrbrdr + 1
2997          IF (dbg) PRINT *,'    ',Nbrbrdr,' Consec brdrs:', halo_brdr(ix+1,j+1), halo_brdr(ix+1,j+2), &
2998             '(', ix,j,';', ix,j+1,')', isbrdr(ix,j), isbrdr(ix,j+1)
2999        ELSE
3000          ! Will remove that consecutive borders above 2
3001          IF (Nbrbrdr /= 0) THEN
3002            IF (dbg) PRINT *, ix,',',iy,';', Nintersecs, '  amount of consecutive borders:', Nbrbrdr, &
3003              ' removing:', MAX(Nbrbrdr-1, 0)
3004            Nintersecs = Nintersecs - MAX(Nbrbrdr-1, 0)
3005            Nbrbrdr = 0
3006          END IF
3007        END IF
3008      END DO
3009      IF (MOD(Nintersecs,2) /= 0) inside(ip) = .TRUE.
3010      IF (dbg) PRINT *,ip,'    point:', ix, iy, 'isbrdr:', isbrdr(ix,1:iy-1), 'y-ray:', halo_brdr(ix+1,1:iy), 'inside:', inside(ip)
3011    END IF
3012
3013  END DO
3014
3015  RETURN
3016
3017END SUBROUTINE gridpoints_InsidePolygon
3018
3019
3020  SUBROUTINE gridpoints_InsidePolygon_ray(dbg, dy, isbrdr, Npath, path, Nvrtx, xpathxtrm, ypathxtrm,  &
3021    vrtxs, Npts, pts, inside)
3022! Subroutine to determine if a series of grid points are inside a polygon following ray casting algorithm
3023! FROM: https://en.wikipedia.org/wiki/Point_in_polygon
3024
3025  IMPLICIT NONE
3026
3027  INTEGER, INTENT(in)                                    :: dy,Npath,Nvrtx,Npts
3028  LOGICAL, INTENT(in)                                    :: dbg
3029  LOGICAL, DIMENSION(dy), INTENT(in)                     :: isbrdr
3030  INTEGER, DIMENSION(Npath,2), INTENT(in)                :: path
3031  INTEGER, DIMENSION(2), INTENT(in)                      :: xpathxtrm, ypathxtrm
3032  INTEGER, DIMENSION(Npath,2)                            :: vrtxs
3033  INTEGER, DIMENSION(dy,2), INTENT(in)                   :: pts
3034  LOGICAL, DIMENSION(Npts), INTENT(out)                  :: inside
3035
3036! Local
3037  INTEGER                                                :: i,j,ip,ix,iy
3038  INTEGER                                                :: Nintersecs, isvertex, ispath
3039  INTEGER                                                :: ierr
3040  LOGICAL, DIMENSION(:), ALLOCATABLE                     :: halo_brdr
3041  INTEGER                                                :: Nbrbrdr
3042
3043!!!!!!! Variables
3044! dy: y-axis space size
3045! Npath: number of points of the path of the polygon
3046! path: path of the polygon
3047! isbrdr: boolean matrix of the space wqith .T. on polygon border
3048! Nvrtx: number of vertexs of the path
3049! [x/y]pathxtrm extremes of the path
3050! vrtxs: vertexs of the path along y-axis
3051! Npts: number of points
3052! pts: points to look for
3053! inside: vector wether point is inside or not (coincident to a border is inside)
3054
3055  fname = 'gridpoints_InsidePolygon_ray'
3056
3057  ! Creation of a 1-grid point larger matrix to deal with points reaching the limits
3058  IF (ALLOCATED(halo_brdr)) DEALLOCATE(halo_brdr)
3059  ALLOCATE(halo_brdr(dy+2), STAT=ierr)
3060  msg = "Problems allocating matrix 'halo_brdr'"
3061  CALL ErrMsg(msg, fname, ierr)
3062  halo_brdr = .FALSE.
3063
3064  IF (dbg) PRINT *,'Border _______'
3065  halo_brdr(2:dy+1) = isbrdr(:)
3066  IF (dbg) PRINT *,isbrdr(:)
3067
3068  inside = .FALSE.
3069
3070  DO ip=1,dy
3071    Nintersecs = 0
3072    ix = pts(ip,1)
3073    iy = pts(ip,2)
3074    ! Point might be outside path range...
3075    IF (ix >= xpathxtrm(1) .AND. ix <= xpathxtrm(2) .AND. iy >= ypathxtrm(1) .AND.                    &
3076      iy <= ypathxtrm(2)) THEN
3077
3078      ! It is a border point?
3079      ispath = index_list_coordsI(Npath, path, (/ix,iy/))
3080      IF (isbrdr(iy) .AND. (ispath /= -1)) THEN
3081        inside(ip) = .TRUE.
3082        CYCLE
3083      END IF
3084
3085      ! Looking along y-axis
3086      ! Accounting for consecutives borders
3087      Nbrbrdr = 0
3088      DO j=MAX(1,ypathxtrm(1)-1),iy-1
3089        ! Only counting that borders that are not vertexs
3090        ispath = index_list_coordsI(Npath, path, (/ix,j/))
3091        isvertex = index_list_coordsI(Npath, vrtxs, (/ix,j/))
3092
3093        IF (halo_brdr(j+1) .AND. (ispath /= -1) .AND. (isvertex == -1) ) Nintersecs = Nintersecs + 1
3094        IF (halo_brdr(j+1) .AND. (ispath /= -1) .AND. (halo_brdr(j+1) .EQV. halo_brdr(j+2))) THEN
3095          Nbrbrdr = Nbrbrdr + 1
3096          IF (dbg) PRINT *,'    ',Nbrbrdr,' Consec brdrs:', halo_brdr(j+1), halo_brdr(j+2), '(',      &
3097             ix,j,';', ix,j+1,')', '(', ix,j,';', ix,j+1,')', isbrdr(j), isbrdr(j+1)
3098        ELSE
3099          ! Will remove that consecutive borders above 2
3100          IF (Nbrbrdr /= 0) THEN
3101            IF (dbg) PRINT *, ix,',',iy,';', Nintersecs, '  amount of consecutive borders:', Nbrbrdr, &
3102              ' removing:', MAX(Nbrbrdr-1, 0)
3103            Nintersecs = Nintersecs - MAX(Nbrbrdr-1, 0)
3104            Nbrbrdr = 0
3105          END IF
3106        END IF
3107      END DO
3108      IF (MOD(Nintersecs,2) /= 0) inside(ip) = .TRUE.
3109      IF (dbg) PRINT *,ip,'    point:', ix, iy, 'isbrdr:', isbrdr(1:iy-1), 'y-ray:', halo_brdr(1:iy), &
3110        'inside:', inside(ip)
3111    END IF
3112
3113  END DO
3114
3115  RETURN
3116
3117END SUBROUTINE gridpoints_InsidePolygon_ray
3118
3119SUBROUTINE look_clockwise_borders(dx,dy,Nbrdrs,brdrs,gbrdr,isbrdr,ix,iy,dbg,xf,yf,iff)
3120! Subroutine to look clock-wise for a next point within a collection of borders (limits of a region)
3121
3122  IMPLICIT NONE
3123
3124  INTEGER, INTENT(in)                                    :: dx, dy, Nbrdrs, ix, iy
3125  INTEGER, DIMENSION(Nbrdrs,2), INTENT(in)               :: brdrs
3126  LOGICAL, DIMENSION(Nbrdrs), INTENT(in)                 :: gbrdr
3127  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: isbrdr
3128  LOGICAL, INTENT(in)                                    :: dbg
3129  INTEGER, INTENT(out)                                   :: xf, yf, iff
3130
3131! Local
3132  INTEGER                                                :: isch
3133  CHARACTER(len=2), DIMENSION(8)                         :: Lclock
3134  INTEGER, DIMENSION(8,2)                                :: spt
3135  INTEGER                                                :: iif, jjf
3136
3137!!!!!!! Variables
3138! dx, dy: 2D shape ot the space
3139! Nbrdrs: number of brdrs found in this 2D space
3140! brdrs: list of coordinates of the borders
3141! gbrdr: accounts for the use if the given border point
3142! isbrdr: accounts for the matrix of the point is a border or not
3143! ix,iy: coordinates of the point to start to find for
3144! xf,yf: coordinates of the found point
3145! iff: position of the border found within the list of borders
3146
3147  fname = 'look_clockwise_borders'
3148
3149  ! Looking clock-wise assuming that one starts from the westernmost point
3150
3151  ! Label of the search
3152  lclock = (/ 'W ', 'NW', 'N ', 'NE', 'E ', 'SE', 'S ', 'SW' /)
3153  ! Transformation to apply
3154  !spt = (/ (/-1,0/), (/-1,1/), (/0,1/), (/1,1/), (/1,0/), (/1,-1/), (/0,-1/), (/-1,-1/) /)
3155  spt(:,1) = (/ -1, -1, 0, 1, 1, 1, 0, -1 /)
3156  spt(:,2) = (/ 0, 1, 1, 1, 0, -1, -1, -1 /)
3157
3158  xf = -1
3159  yf = -1
3160  DO isch=1, 8
3161    ! clock-wise search
3162    IF (spt(isch,1) >= 0) THEN
3163      iif = MIN(dx,ix+spt(isch,1))
3164    ELSE
3165      iif = MAX(1,ix+spt(isch,1))
3166    END IF
3167    IF (spt(isch,2) >= 0) THEN
3168      jjf = MIN(dy,iy+spt(isch,2))
3169    ELSE
3170      jjf = MAX(1,iy+spt(isch,2))
3171    END IF
3172    iff = index_list_coordsI(Nbrdrs, brdrs,(/iif,jjf/))
3173    IF (iff > 0) THEN
3174      IF (dbg) PRINT *,'    ' // lclock(isch) // '-point:', iif,jjf, ':', iff, 'is',isbrdr(iif,jjf),  &
3175        'got',gbrdr(iff)
3176      IF (isbrdr(iif,jjf) .AND. .NOT.gbrdr(iff)) THEN
3177        xf = iif
3178        yf = jjf
3179        EXIT
3180      END IF
3181    END IF
3182  END DO
3183
3184  RETURN
3185
3186END SUBROUTINE look_clockwise_borders
3187
3188SUBROUTINE borders_matrixL(dbg,dx,dy,dxy,Lmat,brdrs,isbrdr,isbrdry)
3189! Subroutine to provide the borders of a logical array (interested in .TRUE.)
3190
3191  IMPLICIT NONE
3192
3193  INTEGER, INTENT(in)                                    :: dx,dy,dxy
3194  LOGICAL, INTENT(in)                                    :: dbg
3195  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: Lmat
3196  INTEGER, DIMENSION(dxy,2), INTENT(out)                 :: brdrs
3197  LOGICAL, DIMENSION(dx,dy), INTENT(out)                 :: isbrdr, isbrdry
3198
3199! Local
3200  INTEGER                                                :: i,j,ib
3201
3202!!!!!!! Variables
3203! dx,dy: size of the space
3204! dxy: maximum number of border points
3205! Lmat: Matrix to look for the borders
3206! brdrs: list of coordinates of the borders
3207! isbrdr: matrix with .T./.F. wether the given matrix point is a border or not
3208! isbrdry: matrix with .T./.F. wether the given matrix point is a border or not only along y-axis
3209
3210  fname = 'borders_matrixL'
3211
3212  isbrdr = .FALSE.
3213  brdrs = -1
3214  ib = 1
3215
3216  ! Starting with the borders. If a given point is TRUE it is a path-vertex
3217  ! Along y-axis
3218  DO i=1, dx
3219    IF (Lmat(i,1) .AND. .NOT.isbrdr(i,1)) THEN
3220      brdrs(ib,1) = i
3221      brdrs(ib,2) = 1
3222      isbrdr(i,1) = .TRUE.
3223      ib=ib+1
3224    END IF
3225    IF (Lmat(i,dy) .AND. .NOT.isbrdr(i,dy)) THEN
3226      brdrs(ib,1) = i
3227      brdrs(ib,2) = dy
3228      isbrdr(i,dy) = .TRUE.
3229      ib=ib+1
3230    END IF
3231  END DO
3232  ! Along x-axis
3233  DO j=1, dy
3234    IF (Lmat(1,j) .AND. .NOT.isbrdr(1,j)) THEN
3235      brdrs(ib,1) = 1
3236      brdrs(ib,2) = j
3237      isbrdr(1,j) = .TRUE.
3238      ib=ib+1
3239     END IF
3240    IF (Lmat(dx,j) .AND. .NOT.isbrdr(dx,j)) THEN
3241      brdrs(ib,1) = dx
3242      brdrs(ib,2) = j
3243      isbrdr(dx,j) = .TRUE.
3244      ib=ib+1
3245    END IF
3246  END DO
3247
3248  isbrdry = isbrdr
3249
3250  ! Border as that when looking on x-axis points with Lmat(i) /= Lmat(i+1)
3251  DO i=1, dx-1
3252    DO j=1, dy-1
3253      IF ( Lmat(i,j) .NEQV. Lmat(i+1,j) ) THEN
3254        IF (Lmat(i,j) .AND. .NOT.isbrdr(i,j)) THEN
3255          brdrs(ib,1) = i
3256          brdrs(ib,2) = j
3257          isbrdr(i,j) = .TRUE.
3258          ib=ib+1
3259        ELSE IF (Lmat(i+1,j) .AND. .NOT.isbrdr(i+1,j)) THEN
3260          brdrs(ib,1) = i+1
3261          brdrs(ib,2) = j
3262          isbrdr(i+1,j) = .TRUE.
3263          ib=ib+1
3264        END IF
3265      END IF
3266      ! y-axis
3267      IF ( Lmat(i,j) .NEQV. Lmat(i,j+1) ) THEN
3268        IF (Lmat(i,j) .AND. .NOT.isbrdr(i,j)) THEN
3269          brdrs(ib,1) = i
3270          brdrs(ib,2) = j
3271          isbrdr(i,j) = .TRUE.
3272          isbrdry(i,j) = .TRUE.
3273          ib=ib+1
3274        ELSE IF (Lmat(i,j+1) .AND. .NOT.isbrdr(i,j+1)) THEN
3275          brdrs(ib,1) = i
3276          brdrs(ib,2) = j+1
3277          isbrdr(i,j+1) = .TRUE.
3278          isbrdry(i,j+1) = .TRUE.
3279          ib=ib+1
3280        END IF
3281      END IF
3282    END DO       
3283  END DO
3284
3285  DO i=1, dx-1
3286    DO j=1, dy-1
3287      ! y-axis
3288      IF ( Lmat(i,j) .NEQV. Lmat(i,j+1) ) THEN
3289        IF (Lmat(i,j)) THEN
3290          isbrdry(i,j) = .TRUE.
3291        ELSE IF (Lmat(i,j+1)) THEN
3292          isbrdry(i,j+1) = .TRUE.
3293        END IF
3294      END IF
3295    END DO       
3296  END DO
3297  ! only y-axis adding bands of 2 grid points
3298  DO i=1, dx-1
3299    DO j=2, dy-2
3300      IF ( (Lmat(i,j) .EQV. Lmat(i,j+1)) .AND. (Lmat(i,j).NEQV.Lmat(i,j-1)) .AND. (Lmat(i,j).NEQV.Lmat(i,j+2)) ) THEN
3301        IF (Lmat(i,j)) THEN
3302          isbrdry(i,j) = .TRUE.
3303          isbrdry(i,j+1) = .TRUE.
3304        END IF
3305      END IF
3306    END DO       
3307  END DO
3308
3309  IF (dbg) THEN
3310    PRINT *,' BORDERS _______ x y'
3311    DO i=1,dx
3312      PRINT *,isbrdr(i,:), '       ', isbrdry(i,:)
3313    END DO
3314  END IF
3315
3316  RETURN
3317
3318END SUBROUTINE borders_matrixL
3319
3320SUBROUTINE paths_border(dbg, dx, dy, isborder, Nppt, borders, paths, Npath, Nptpaths)
3321! Subroutine to search the paths of a border field.
3322
3323  IMPLICIT NONE
3324
3325  INTEGER, INTENT(in)                                    :: dx, dy, Nppt
3326  LOGICAL, INTENT(in)                                    :: dbg
3327  LOGICAL, DIMENSION(dx,dy), INTENT(in)                  :: isborder
3328  INTEGER, DIMENSION(Nppt,2), INTENT(in)                 :: borders
3329  INTEGER, DIMENSION(Nppt,Nppt,2), INTENT(out)           :: paths
3330  INTEGER, INTENT(out)                                   :: Npath
3331  INTEGER, DIMENSION(Nppt), INTENT(out)                  :: Nptpaths
3332
3333! Local
3334  INTEGER                                                :: i,j,k,ib
3335  INTEGER                                                :: ierr
3336  INTEGER                                                :: Nbrdr
3337  LOGICAL, DIMENSION(:), ALLOCATABLE                     :: gotbrdr, emptygotbrdr
3338  INTEGER                                                :: iipth, ipath, ip, Nptspath
3339  INTEGER                                                :: iib, jjb, iip, ijp, iif, jjf, iff
3340  LOGICAL                                                :: found, finishedstep
3341
3342!!!!!!! Variables
3343! dx,dy: spatial dimensions of the space
3344! Nppt: possible number of paths and points that the paths can have
3345! isborder: boolean matrix which provide the borders of the polygon
3346! borders: coordinates of the borders of the polygon
3347! paths: coordinates of each found path
3348! Npath: number of paths found
3349! Nptpaths: number of points per path
3350
3351  fname = 'paths_border'
3352
3353  IF (dbg) PRINT *, TRIM(fname) // ' ...'
3354
3355  ! Sarting matrix
3356  paths = -1
3357  Npath = 0
3358  Nptspath = 0
3359  Nptpaths = -1
3360
3361  ib=1
3362  finishedstep = .FALSE.
3363
3364  ! Number of border points
3365  DO ib=1, Nppt
3366    IF (borders(ib,1) == -1 ) EXIT
3367  END DO
3368  Nbrdr = ib-1
3369   
3370  IF (dbg) THEN
3371    PRINT *,'  isborder ______'
3372    DO i=1,dx
3373      PRINT *,isborder(i,:)
3374    END DO
3375
3376    PRINT *,'    borders _______'
3377    DO i=1,Nbrdr
3378      PRINT *,'    ',i,':',borders(i,:)
3379    END DO
3380  END IF
3381
3382  ! Matrix which keeps track if a border point has been located
3383  IF (ALLOCATED(gotbrdr)) DEALLOCATE(gotbrdr)
3384  ALLOCATE(gotbrdr(Nbrdr), STAT=ierr)
3385  msg = "Problems allocating matrix 'gotbrdr'"
3386  CALL ErrMsg(msg, fname, ierr)
3387  IF (ALLOCATED(emptygotbrdr)) DEALLOCATE(emptygotbrdr)
3388  ALLOCATE(emptygotbrdr(Nbrdr), STAT=ierr)
3389  msg = "Problems allocating matrix 'emptygotbrdr'"
3390  CALL ErrMsg(msg, fname, ierr)
3391
3392  gotbrdr = .FALSE.
3393  emptygotbrdr = .FALSE.
3394
3395  ! Starting the fun...
3396   
3397  ! Looking along the lines and when a border is found, starting from there in a clock-wise way
3398  iipth = 1
3399  ipath = 1   
3400  DO ib=1,Nbrdr
3401    iib = borders(iipth,1)
3402    jjb = borders(iipth,2)
3403    ! Starting new path
3404    newpath: IF (.NOT.gotbrdr(iipth)) THEN
3405      ip = 1
3406      Nptspath = 1
3407      paths(ipath,ip,:) = borders(iipth,:)
3408      gotbrdr(iipth) = .TRUE.
3409      ! Looking for following clock-wise search
3410      ! Not looking for W, because search starts from the W
3411      iip = iib
3412      ijp = jjb
3413      DO k=1,Nbrdr
3414        IF (dbg) PRINT *,ipath,'iip jip:', iip, ijp
3415        found = .FALSE.
3416        CALL look_clockwise_borders(dx,dy,Nppt,borders,gotbrdr,isborder,iip,ijp,dbg,iif,jjf,iff)
3417        IF (iif /= -1) THEN
3418          ip=ip+1
3419          paths(ipath,ip,:) = (/ iif,jjf /)
3420          found = .TRUE.
3421          gotbrdr(iff) = .TRUE.
3422          iip = iif
3423          ijp = jjf
3424          Nptspath = Nptspath + 1         
3425        END IF
3426
3427        IF (dbg) THEN
3428          PRINT *,iib,jjb,'    end of this round path:', ipath, '_____', gotbrdr
3429          DO i=1, Nptspath
3430            PRINT *,'      ',i,':',paths(ipath,i,:)
3431          END DO
3432        END IF
3433        ! If it is not found a next point, might be because it is a non-polygon related value
3434        IF (.NOT.found) THEN
3435          IF (dbg) PRINT *,'NOT FOUND !!!', gotbrdr
3436          ! Are still there available borders? 
3437          IF (ALL(gotbrdr) .EQV. .TRUE.) THEN
3438            finishedstep = .TRUE.
3439            Npath = ipath
3440            Nptpaths(ipath) = Nptspath
3441            EXIT
3442          ELSE
3443            Nptpaths(ipath) = Nptspath
3444            ! Let's have a look if the previous points in the path have already some 'non-located' neighbourgs
3445            DO i=Nptspath,1,-1
3446              iip = paths(ipath,i,1)
3447              ijp = paths(ipath,i,2)
3448              CALL look_clockwise_borders(dx,dy,Nppt,borders, gotbrdr, isborder,iip, ijp, dbg, iif,   &
3449                jjf,iff)
3450              IF (iif /= -1 .AND. iff /= -1) THEN
3451                IF (dbg) PRINT *,'    re-take path from point:', iif,',',jjf,' n-path:', iff
3452                found = .TRUE.
3453                iipth = index_list_coordsI(Nppt, borders, (/iip,ijp/))
3454                EXIT
3455              END IF
3456            END DO
3457            IF (.NOT.found) THEN
3458              ! Looking for the next available border point for the new path
3459              DO i=1,Nbrdr
3460                IF (.NOT.gotbrdr(i)) THEN
3461                  iipth = i
3462                  EXIT
3463                END IF
3464              END DO
3465              IF (dbg) PRINT *,'  Looking for next path starting at:', iipth, ' point:',              &
3466                borders(iipth,:)
3467              ipath=ipath+1
3468              EXIT
3469            END IF
3470          END IF
3471        ELSE
3472          IF (dbg) PRINT *,'  looking for next point...'
3473        END IF
3474        IF (finishedstep) EXIT
3475      END DO
3476    END IF newpath
3477  END DO
3478  Npath = ipath
3479  Nptpaths(ipath) = Nptspath
3480   
3481  DEALLOCATE (gotbrdr)
3482  DEALLOCATE (emptygotbrdr)
3483
3484  RETURN
3485
3486END SUBROUTINE paths_border
3487
3488SUBROUTINE rand_sample(Nvals, Nsample, sample)
3489! Subroutine to randomly sample a range of indices
3490
3491  IMPLICIT NONE
3492
3493  INTEGER, INTENT(in)                                    :: Nvals, Nsample
3494  INTEGER, DIMENSION(Nsample), INTENT(out)               :: sample
3495
3496! Local
3497  INTEGER                                                :: i, ind, jmax
3498  REAL, DIMENSION(Nsample)                               :: randv
3499  CHARACTER(len=50)                                      :: fname
3500  LOGICAL                                                :: found
3501  LOGICAL, DIMENSION(Nvals)                              :: issampled
3502  CHARACTER(len=256)                                     :: msg
3503  CHARACTER(len=10)                                      :: IS1, IS2
3504
3505!!!!!!! Variables
3506! Nvals: number of values
3507! Nsamples: number of samples
3508! sample: samnple
3509  fname = 'rand_sample'
3510
3511  IF (Nsample > Nvals) THEN
3512    WRITE(IS1,'(I10)')Nvals
3513    WRITE(IS2,'(I10)')Nsample
3514    msg = 'Sampling of ' // TRIM(IS1) // ' is too big for ' // TRIM(IS1) // 'values'
3515    CALL ErrMsg(msg, fname, -1)
3516  END IF
3517
3518  ! Generation of random numbers always the same series during the whole program!
3519  CALL RANDOM_NUMBER(randv)
3520
3521  ! Making sure that we do not repeat any value
3522  issampled = .FALSE.
3523
3524  DO i=1, Nsample
3525    ! Generation of the index from the random numbers
3526    ind = MAX(INT(randv(i)*Nvals), 1)
3527
3528    IF (.NOT.issampled(ind)) THEN
3529      sample(i) = ind
3530      issampled(ind) = .TRUE.
3531    ELSE
3532      ! Looking around the given index
3533      !PRINT *,' Index :', ind, ' already sampled!', issampled(ind)
3534      found = .FALSE.
3535      DO jmax=1, Nvals
3536        ind = MIN(ind+jmax, Nvals)
3537        IF (.NOT.issampled(ind)) THEN
3538          sample(i) = ind
3539          issampled(ind) = .TRUE.
3540          found = .TRUE.
3541          EXIT
3542        END IF
3543        ind = MAX(1, ind-jmax)
3544        IF (.NOT.issampled(ind)) THEN
3545          sample(i) = ind
3546          issampled(ind) = .TRUE.
3547          found = .TRUE.
3548          EXIT
3549        END IF
3550      END DO
3551      IF (.NOT.found) THEN
3552        msg = 'sampling could not be finished due to absence of available value!!'
3553        CALL ErrMsg(msg, fname, -1)
3554      END IF
3555    END IF
3556
3557  END DO
3558
3559  RETURN
3560
3561END SUBROUTINE rand_sample
3562
3563SUBROUTINE PrintQuantilesR_K(Nvals, vals, Nquants, qtvs, bspc)
3564! Subroutine to print the quantiles of values REAL(r_k)
3565
3566  IMPLICIT NONE
3567
3568  INTEGER, INTENT(in)                                    :: Nvals, Nquants
3569  REAL(r_k), DIMENSION(Nvals), INTENT(in)                :: vals
3570  REAL(r_k), DIMENSION(Nquants), INTENT(in)              :: qtvs
3571  CHARACTER(len=1000), OPTIONAL                          :: bspc
3572
3573! Local
3574  INTEGER                                                :: iq
3575  LOGICAL, DIMENSION(Nvals)                              :: search1, search2, search
3576  CHARACTER(len=6)                                       :: RS1
3577  CHARACTER(len=50)                                      :: fname
3578  CHARACTER(len=1000)                                    :: bspcS
3579
3580!!!!!!! Variables
3581! vals: series of values
3582! qtvs: values of the quantiles
3583! bspc: base quantity of spaces
3584
3585  fname = 'PrintQuantilesR_K'
3586
3587  IF (PRESENT(bspc)) THEN
3588    bspcS = bspc
3589  ELSE
3590    bspcS = '      '
3591  END IF
3592
3593  DO iq=1, Nquants-1
3594
3595    WHERE (vals >= qtvs(iq))
3596      search1 = .TRUE.
3597    ELSEWHERE
3598      search1 = .FALSE.
3599    END WHERE
3600
3601    WHERE (vals < qtvs(iq+1))
3602      search2 = .TRUE.
3603    ELSEWHERE
3604      search2 = .FALSE.
3605    END WHERE
3606
3607    WHERE (search1 .AND. search2)
3608      search = .TRUE.
3609    ELSEWHERE
3610      search = .FALSE.
3611    END WHERE
3612
3613    WRITE(RS1, '(F6.2)')(iq)*100./(Nquants-1)
3614    PRINT *, TRIM(bspcS) // '[',iq,']', TRIM(RS1) // ' %:', qtvs(iq), 'N:', COUNT(search)
3615
3616  END DO
3617
3618  RETURN
3619
3620END SUBROUTINE PrintQuantilesR_K
3621
3622   INTEGER FUNCTION FindMinimumR_K(x, dsize, Startv, Endv)
3623! Function returns the location of the minimum in the section between Start and End.
3624
3625      IMPLICIT NONE
3626
3627      INTEGER, INTENT(in)                                :: dsize
3628      REAL(r_k), DIMENSION(dsize), INTENT(in)            :: x
3629      INTEGER, INTENT(in)                                :: Startv, Endv
3630
3631! Local
3632      REAL(r_k)                                          :: Minimum
3633      INTEGER                                            :: Location
3634      INTEGER                                            :: i
3635
3636      Minimum  = x(Startv)                               ! assume the first is the min
3637      Location = Startv                                  ! record its position
3638      DO i = Startv+1, Endv                              ! start with next elements
3639         IF (x(i) < Minimum) THEN                        !   if x(i) less than the min?
3640            Minimum  = x(i)                              !      Yes, a new minimum found
3641            Location = i                                 !      record its position
3642         END IF
3643      END DO
3644
3645      FindMinimumR_K = Location                          ! return the position
3646
3647   END FUNCTION  FindMinimumR_K
3648
3649   SUBROUTINE SwapR_K(a, b)
3650! Subroutine swaps the values of its two formal arguments.
3651
3652      IMPLICIT NONE
3653
3654      REAL(r_k), INTENT(INOUT)                           :: a, b
3655! Local
3656      REAL(r_k)                                          :: Temp
3657
3658      Temp = a
3659      a    = b
3660      b    = Temp
3661
3662   END SUBROUTINE  SwapR_K
3663
3664   SUBROUTINE  SortR_K(x, Nx)
3665! Subroutine receives an array x() r_K and sorts it into ascending order.
3666
3667      IMPLICIT NONE
3668
3669      INTEGER, INTENT(IN)                                :: Nx
3670      REAL(r_k), DIMENSION(Nx), INTENT(INOUT)            :: x
3671
3672! Local
3673      INTEGER                                            :: i
3674      INTEGER                                            :: Location
3675
3676      DO i = 1, Nx-1                                     ! except for the last
3677         Location = FindMinimumR_K(x, Nx-i+1, i, Nx)     ! find min from this to last
3678         CALL  SwapR_K(x(i), x(Location))                ! swap this and the minimum
3679      END DO
3680
3681   END SUBROUTINE  SortR_K
3682
3683SUBROUTINE quantilesR_K(Nvals, vals, Nquants, quants)
3684! Subroutine to provide the quantiles of a given set of values of type real 'r_k'
3685
3686  IMPLICIT NONE
3687
3688  INTEGER, INTENT(in)                                    :: Nvals, Nquants
3689  REAL(r_k), DIMENSION(Nvals), INTENT(in)                :: vals
3690  REAL(r_k), DIMENSION(Nquants), INTENT(out)             :: quants
3691
3692! Local
3693  INTEGER                                                :: i
3694  REAL(r_k)                                              :: minv, maxv
3695  REAL(r_k), DIMENSION(Nvals)                            :: sortedvals
3696
3697!!!!!!! Variables
3698! Nvals: number of values
3699! Rk: kind of real of the values
3700! vals: values
3701! Nquants: number of quants
3702! quants: values at which the quantile start
3703
3704  minv = MINVAL(vals)
3705  maxv = MAXVAL(vals)
3706
3707  sortedvals = vals
3708  ! Using from: http://www.cs.mtu.edu/~shene/COURSES/cs201/NOTES/chap08/sorting.f90
3709  CALL SortR_K(sortedvals, Nvals)
3710
3711  quants(1) = minv
3712  DO i=2, Nquants
3713    quants(i) = sortedvals(INT((i-1)*Nvals/Nquants))
3714  END DO
3715
3716END SUBROUTINE quantilesR_K
3717
3718
3719SUBROUTINE StatsR_K(Nvals, vals, minv, maxv, mean, mean2, stdev)
3720! Subroutine to provide the minmum, maximum, mean, the quadratic mean, and the standard deviation of a
3721!   series of r_k numbers
3722
3723  IMPLICIT NONE
3724
3725  INTEGER, INTENT(in)                                    :: Nvals
3726  REAL(r_k), DIMENSION(Nvals), INTENT(in)                :: vals
3727  REAL(r_k), INTENT(out)                                 :: minv, maxv, mean, mean2, stdev
3728
3729!!!!!!! Variables
3730! Nvals: number of values
3731! vals: values
3732! minv: minimum value of values
3733! maxv: maximum value of values
3734! mean: mean value of values
3735! mean2: quadratic mean value of values
3736! stdev: standard deviation of values
3737
3738  minv = MINVAL(vals)
3739  maxv = MAXVAL(vals)
3740
3741  mean=SUM(vals)
3742  mean2=SUM(vals*vals)
3743
3744  mean=mean/Nvals
3745  mean2=mean2/Nvals
3746
3747  stdev=SQRT(mean2 - mean*mean)
3748
3749  RETURN
3750
3751END SUBROUTINE StatsR_k
3752
3753  SUBROUTINE NcountR(values, d1, Ndiffvals, counts)
3754! Subroutine to count real values
3755
3756    IMPLICIT NONE
3757
3758    INTEGER, INTENT(in)                                  :: d1
3759    REAL(r_k), DIMENSION(d1), INTENT(in)                 :: values
3760    INTEGER, INTENT(out)                                 :: Ndiffvals
3761    REAL(r_k), DIMENSION(d1,2), INTENT(out)              :: counts
3762! Local
3763    INTEGER                                              :: i, ival
3764    REAL(r_k), DIMENSION(d1)                             :: diffv
3765
3766!!!!!!! Variables
3767! values: values to count
3768! counts: counts of time for each value
3769   
3770    fname = 'NcountR'
3771
3772    counts = -1.
3773
3774    counts(1,1) = values(1)
3775    counts(1,2) = 1
3776    Ndiffvals = 1
3777    DO i=2,d1
3778      diffv(1:Ndiffvals) = counts(1:Ndiffvals,1) - values(i)
3779      IF (ANY(diffv(1:Ndiffvals) == 0)) THEN
3780        ival = Index1DArrayR(counts(1:Ndiffvals,1), Ndiffvals, values(i))
3781        counts(ival,2) = counts(ival,2) + 1
3782      ELSE
3783        Ndiffvals = Ndiffvals + 1
3784        counts(Ndiffvals,1) = values(i)
3785        counts(Ndiffvals,2) = 1
3786      END IF
3787    END DO
3788
3789  END SUBROUTINE NcountR
3790
3791  SUBROUTINE runmean_F1D(d1, values, Nmean, headertail, runmean)
3792! Subroutine fo computing the running mean of a given set of float 1D values
3793
3794  IMPLICIT NONE
3795
3796  INTEGER, INTENT(in)                                    :: d1, Nmean
3797  REAL(r_k), DIMENSION(d1), INTENT(in)                   :: values
3798  CHARACTER(len=*), INTENT(in)                           :: headertail
3799  REAL(r_k), DIMENSION(d1), INTENT(out)                  :: runmean
3800 
3801! Local
3802  INTEGER                                                :: i, j, Nmean2
3803  CHARACTER(len=5)                                       :: NmeanS
3804
3805!!!!!!! Variables
3806! values: values to compute the running mean
3807! Nmean: number of odd points to use for the running mean
3808! headertail: How to proceed for the grid points at the beginning of the values which are not
3809!   encompassed by the Nmean
3810!   'miss': set as missing values (1.d20)
3811!   'original': keep the original values
3812!   'progressfill': mean the values as a progressive running filter (e.g. for Nmean=5):
3813!     runmean[values(1)] = values(1)
3814!     runmean[values(2)] = MEAN(values(1:3))
3815!     runmean[values(3)] = MEAN(values(1:5))
3816!     runmean[values(4)] = MEAN(values(2:6))
3817!     (...)
3818!     runmean[values(d1-2)] = MEAN(values(d1-5:d1))
3819!     runmean[values(d1-1)] = MEAN(values(d1-2:d1))
3820!     runmean[values(d1)] = MEAN(values(dd1))
3821!   'zero': set as zero values
3822! runmean: runnig mean values
3823
3824  fname = 'runmean_F1D'
3825
3826  IF (MOD(Nmean,2) == 0) THEN
3827    WRITE(NmeanS,'(I5)')Nmean
3828    msg="Nmean has to be odd!! value provided: "// NmeanS
3829    CALL ErrMsg(msg, fname, -1)
3830  END IF
3831  Nmean2 = Nmean/2
3832 
3833  SELECT CASE (TRIM(headertail))
3834    CASE ('missing')
3835      runmean = fillval64
3836    CASE ('original')
3837      runmean = values
3838    CASE ('progressfill')
3839      DO i=1, Nmean2
3840        runmean(i) = SUM(values(1:2*(i-1)+1))/(2*(i-1)+1)
3841      END DO
3842      runmean(d1) = values(d1)
3843      DO i=2, Nmean2
3844        j = d1-(2*(i-1))
3845        runmean(d1-(i-1)) = SUM(values(j:d1))/(2*(i-1)+1)
3846      END DO
3847    CASE ('zero')
3848      runmean = zeroRK
3849    CASE DEFAULT
3850      msg = "'" // TRIM(headertail) // "' not available !!" //CHAR(44) // "  available ones: " //     &
3851        "'missing', 'original', 'progressfill', 'zero'"
3852      CALL ErrMsg(msg, fname, -1)
3853  END SELECT
3854
3855  DO i= 1+Nmean2, d1 - Nmean2
3856    runmean(i) = SUM(values(i-Nmean2:i+Nmean2))/Nmean
3857  END DO
3858
3859  END SUBROUTINE runmean_F1D
3860
3861  SUBROUTINE percentiles_R_K2D(values, axisS, Npercen, d1, d2, percentiles)
3862  ! Subroutine to compute the percentiles of a 2D R_K array along given set of axis
3863
3864    IMPLICIT NONE
3865 
3866    INTEGER, INTENT(in)                                    :: d1, d2, Npercen
3867    REAL(r_k), DIMENSION(d1,d2), INTENT(in)                :: values
3868    CHARACTER(LEN=*), INTENT(in)                           :: axisS
3869    REAL(r_k), DIMENSION(d1, d2, Npercen), INTENT(out)     :: percentiles
3870
3871    ! Local
3872    INTEGER                                                :: i
3873    INTEGER                                                :: Lstring, LaxisS, iichar
3874    CHARACTER(LEN=1000)                                    :: splitaxis
3875    INTEGER, DIMENSION(1)                                  :: axis1
3876    CHARACTER(LEN=200), DIMENSION(2)                       :: axis2S
3877    INTEGER, DIMENSION(2)                                  :: axis2
3878    CHARACTER(LEN=1)                                       :: Naxs
3879
3880!!!!!!! Variables
3881! d1,d2: length of the 2D dimensions
3882! values: values to use to compute the percentiles
3883! axisS: ':' separated list of axis to use to compute the percentiles ('all' for all axes)
3884! Npercen: number of percentiles
3885! percentiles: percentiles of the daata
3886
3887    fname = 'percentiles_R_K2D'
3888
3889    LaxisS = LEN_TRIM(axisS)
3890    iichar = numberTimes(axisS(1:LaxisS), ':')
3891
3892    splitaxis = ''
3893    splitaxis(1:LaxisS) = axisS(1:LaxisS)
3894    percentiles = 0.
3895
3896    IF (iichar == 0) THEN
3897      READ(axisS,'(I1)')axis1(1)
3898    ELSE IF (iichar == 1) THEN
3899      CALL split(splitaxis, ':', 2, axis2S)
3900    ELSE
3901      WRITE(Naxs,'(A1)')iichar
3902      msg = "' rank 2 values can not compute percentiles using " // Naxs // "' number of axis !!"
3903      CALL ErrMsg(msg, fname, -1)
3904    END IF
3905
3906    IF (TRIM(axisS) == 'all') iichar = 2
3907 
3908    IF (iichar == 0) THEN
3909      ! Might be a better way, but today I can't think it !!
3910      IF (axis1(1) == 1) THEN
3911        DO i=1, d2
3912          CALL quantilesR_K(d1, values(:,i), Npercen, percentiles(1,i,:))
3913        END DO
3914      ELSE IF (axis1(1) == 2) THEN
3915        DO i=1, d1
3916          CALL quantilesR_K(d2, values(i,:), Npercen, percentiles(i,1,:))
3917        END DO
3918      ELSE
3919        WRITE(Naxs,'(A1)')axis1(1)
3920        msg = "' rank 2 values can not compute percentiles using axis " // Naxs // "' !!"
3921        CALL ErrMsg(msg, fname, -1)
3922      END IF
3923    ELSE
3924      CALL quantilesR_K(d1*d2, RESHAPE(values, (/d1*d2/)), Npercen, percentiles(1,1,:))
3925    END IF
3926
3927  END SUBROUTINE percentiles_R_K2D
3928
3929  SUBROUTINE percentiles_R_K3D(values, axisS, Npercen, d1, d2, d3, percentiles)
3930  ! Subroutine to compute the percentiles of a 3D R_K array along given set of axis
3931
3932    IMPLICIT NONE
3933 
3934    INTEGER, INTENT(in)                                    :: d1, d2, d3, Npercen
3935    REAL(r_k), DIMENSION(d1,d2,d3), INTENT(in)             :: values
3936    CHARACTER(LEN=*), INTENT(in)                           :: axisS
3937    REAL(r_k), DIMENSION(d1, d2, d3, Npercen), INTENT(out) :: percentiles
3938
3939    ! Local
3940    INTEGER                                                :: i, j
3941    INTEGER                                                :: Lstring, LaxisS, iichar
3942    CHARACTER(LEN=1000)                                    :: splitaxis
3943    INTEGER, DIMENSION(1)                                  :: axis1
3944    CHARACTER(LEN=200), DIMENSION(2)                       :: axis2S
3945    INTEGER, DIMENSION(2)                                  :: axis2
3946    CHARACTER(LEN=200), DIMENSION(3)                       :: axis3S
3947    INTEGER, DIMENSION(3)                                  :: axis3
3948    CHARACTER(LEN=1)                                       :: Naxs1, Naxs2
3949
3950!!!!!!! Variables
3951! d1,d2: length of the 2D dimensions
3952! values: values to use to compute the percentiles
3953! axisS: ':' separated list of axis to use to compute the percentiles ('all' for all axes)
3954! Npercen: number of percentiles
3955! percentiles: percentiles of the daata
3956
3957    fname = 'percentiles_R_K3D'
3958
3959    LaxisS = LEN_TRIM(axisS)
3960    iichar = numberTimes(axisS(1:LaxisS), ':')
3961
3962    splitaxis = ''
3963    splitaxis(1:LaxisS) = axisS(1:LaxisS)
3964
3965    percentiles = 0.
3966
3967    IF (iichar == 0) THEN
3968      READ(axisS,'(I1)')axis1(1)
3969    ELSE IF (iichar == 1) THEN
3970      CALL split(splitaxis, ':', 2, axis2S)
3971      DO i=1,2
3972        READ(axis2S(i), '(I1)')axis2(i)
3973      END DO
3974    ELSE IF (iichar == 2) THEN
3975      CALL split(splitaxis, ':', 3, axis3S)
3976    ELSE
3977      READ(Naxs1,'(A1)')iichar
3978      msg = "' rank 3 values can not compute percentiles using " // Naxs1 // "' number of axis !!"
3979      CALL ErrMsg(msg, fname, -1)
3980    END IF
3981
3982    IF (TRIM(axisS) == 'all') iichar = 3
3983 
3984    IF (iichar == 0) THEN
3985      ! Might be a better way, but today I can't think it !!
3986      IF (axis1(1) == 1) THEN
3987        DO i=1, d2
3988          DO j=1, d3
3989            CALL quantilesR_K(d1, values(:,i,j), Npercen, percentiles(1,i,j,:))
3990          END DO
3991        END DO
3992      ELSE IF (axis1(1) == 2) THEN
3993        DO i=1, d1
3994          DO j=1, d3
3995            CALL quantilesR_K(d2, values(i,:,j), Npercen, percentiles(i,1,j,:))
3996          END DO
3997        END DO
3998      ELSE IF (axis1(1) == 3) THEN
3999        DO i=1, d1
4000          DO j=1, d2
4001            CALL quantilesR_K(d3, values(i,j,:), Npercen, percentiles(i,j,1,:))
4002          END DO
4003        END DO
4004      ELSE
4005        WRITE(Naxs1,'(A1)')axis1(1)
4006        msg = "' rank 3 values can not compute percentiles using axis " // Naxs1 // "' !!"
4007        CALL ErrMsg(msg, fname, -1)
4008      END IF
4009    ELSE IF (iichar == 1) THEN
4010      ! Might be a better way, but today I can't think it !!
4011      IF (axis2(1) == 1 .AND. axis2(2) == 2) THEN
4012        DO i=1, d3
4013          CALL quantilesR_K(d1*d2, RESHAPE(values(:,:,i), (/d1*d2/)), Npercen, percentiles(1,1,i,:))
4014        END DO
4015      ELSE IF (axis2(1) == 1 .AND. axis2(2) == 3) THEN
4016        DO i=1, d2
4017          CALL quantilesR_K(d1*d3, RESHAPE(values(:,i,:), (/d1*d3/)), Npercen, percentiles(1,i,1,:))
4018        END DO
4019      ELSE IF (axis2(1) == 2 .AND. axis2(2) == 3) THEN
4020        DO i=1, d1
4021          CALL quantilesR_K(d2*d3, RESHAPE(values(i,:,:), (/d2*d3/)), Npercen, percentiles(i,1,1,:))
4022        END DO
4023      ELSE
4024        WRITE(Naxs1,'(A1)')axis2(1)
4025        WRITE(Naxs2,'(A1)')axis2(2)
4026        msg="' rank 3 values can not compute percentiles using axis "//Naxs1// ', ' // Naxs2 // "' !!"
4027        CALL ErrMsg(msg, fname, -1)
4028      END IF
4029    ELSE
4030      CALL quantilesR_K(d1*d2*d3, RESHAPE(values, (/d1*d2*d3/)), Npercen, percentiles(1,1,1,:))
4031    END IF
4032
4033  END SUBROUTINE percentiles_R_K3D
4034
4035  SUBROUTINE percentiles_R_K4D(values, axisS, Npercen, d1, d2, d3, d4, percentiles)
4036  ! Subroutine to compute the percentiles of a 4D R_K array along given set of axis
4037
4038    IMPLICIT NONE
4039 
4040    INTEGER, INTENT(in)                                    :: d1, d2, d3, d4, Npercen
4041    REAL(r_k), DIMENSION(d1,d2,d3,d4), INTENT(in)          :: values
4042    CHARACTER(LEN=*), INTENT(in)                           :: axisS
4043    REAL(r_k), DIMENSION(d1,d2,d3,d4,Npercen), INTENT(out) :: percentiles
4044
4045    ! Local
4046    INTEGER                                                :: i, j, k
4047    INTEGER                                                :: Lstring, LaxisS, iichar
4048    CHARACTER(LEN=1000)                                    :: splitaxis
4049    INTEGER, DIMENSION(1)                                  :: axis1
4050    CHARACTER(LEN=200), DIMENSION(2)                       :: axis2S
4051    INTEGER, DIMENSION(2)                                  :: axis2
4052    CHARACTER(LEN=200), DIMENSION(3)                       :: axis3S
4053    INTEGER, DIMENSION(3)                                  :: axis3
4054    CHARACTER(LEN=200), DIMENSION(4)                       :: axis4S
4055    CHARACTER(LEN=1)                                       :: Naxs1, Naxs2, Naxs3
4056
4057!!!!!!! Variables
4058! d1,d2: length of the 2D dimensions
4059! values: values to use to compute the percentiles
4060! axisS: ':' separated list of axis to use to compute the percentiles ('all' for all axes)
4061! Npercen: number of percentiles
4062! percentiles: percentiles of the daata
4063
4064    fname = 'percentiles_R_K3D'
4065
4066    LaxisS = LEN_TRIM(axisS)
4067    iichar = numberTimes(axisS(1:LaxisS), ':')
4068
4069    splitaxis = ''
4070    splitaxis(1:LaxisS) = axisS(1:LaxisS)
4071
4072    percentiles = 0.
4073
4074    PRINT *,'iichar:', iichar, axisS(1:LaxisS)
4075
4076    IF (iichar == 0) THEN
4077      READ(axisS,'(I1)')axis1(1)
4078    ELSE IF (iichar == 1) THEN
4079      CALL split(splitaxis, ':', 2, axis2S)
4080      DO i=1,2
4081        READ(axis2S(i), '(I1)')axis2(i)
4082      END DO
4083    ELSE IF (iichar == 2) THEN
4084      CALL split(splitaxis, ':', 3, axis3S)
4085      DO i=1,3
4086        READ(axis3S(i), '(I1)')axis3(i)
4087      END DO
4088    ELSE IF (iichar == 3) THEN
4089      CALL split(splitaxis, ':', 4, axis4S)
4090    ELSE
4091      READ(Naxs1,'(A1)')iichar
4092      msg = "' rank 4 values can not compute percentiles using " // Naxs1 // "' number of axis !!"
4093      CALL ErrMsg(msg, fname, -1)
4094    END IF
4095
4096    IF (TRIM(axisS) == 'all') iichar = 4
4097 
4098    IF (iichar == 0) THEN
4099      ! Might be a better way, but today I can't think it !!
4100      IF (axis1(1) == 1) THEN
4101        DO i=1, d2
4102          DO j=1, d3
4103            DO k=1, d4
4104              CALL quantilesR_K(d1, values(:,i,j,k), Npercen, percentiles(1,i,j,k,:))
4105            END DO
4106          END DO
4107        END DO
4108      ELSE IF (axis1(1) == 2) THEN
4109        DO i=1, d1
4110          DO j=1, d3
4111            DO k=1, d4
4112              CALL quantilesR_K(d2, values(i,:,j,k), Npercen, percentiles(i,1,j,k,:))
4113            END DO
4114          END DO
4115        END DO
4116      ELSE IF (axis1(1) == 3) THEN
4117        DO i=1, d1
4118          DO j=1, d2
4119            DO k=1, d4
4120              CALL quantilesR_K(d3, values(i,j,:,k), Npercen, percentiles(i,j,1,k,:))
4121            END DO
4122          END DO
4123        END DO
4124      ELSE IF (axis1(1) == 4) THEN
4125        DO i=1, d1
4126          DO j=1, d2
4127            DO k=1, d3
4128              CALL quantilesR_K(d4, values(i,j,k,:), Npercen, percentiles(i,j,k,1,:))
4129            END DO
4130          END DO
4131        END DO
4132      ELSE
4133        WRITE(Naxs1,'(A1)')axis1(1)
4134        msg = "' rank 3 values can not compute percentiles using axis " // Naxs1 // "' !!"
4135        CALL ErrMsg(msg, fname, -1)
4136      END IF
4137    ELSE IF (iichar == 1) THEN
4138      ! Might be a better way, but today I can't think it !!
4139      IF (axis2(1) == 1 .AND. axis2(2) == 2) THEN
4140        DO i=1, d3
4141          DO j=1, d4
4142            CALL quantilesR_K(d1*d2, RESHAPE(values(:,:,i,j), (/d1*d2/)), Npercen,                    &
4143              percentiles(1,1,i,j,:))
4144          END DO
4145        END DO
4146      ELSE IF (axis2(1) == 1 .AND. axis2(2) == 3) THEN
4147        DO i=1, d2
4148          DO j=1, d4
4149            CALL quantilesR_K(d1*d3, RESHAPE(values(:,i,:,j), (/d1*d3/)), Npercen,                    &
4150              percentiles(1,i,1,j,:))
4151          END DO
4152        END DO
4153      ELSE IF (axis2(1) == 1 .AND. axis2(2) == 4) THEN
4154        DO i=1, d2
4155          DO j=1, d3
4156            CALL quantilesR_K(d1*d4, RESHAPE(values(:,i,j,:), (/d1*d4/)), Npercen,                    &
4157              percentiles(1,i,j,1,:))
4158          END DO
4159        END DO
4160      ELSE IF (axis2(1) == 2 .AND. axis2(2) == 3) THEN
4161        DO i=1, d1
4162          DO j=1, d4
4163            CALL quantilesR_K(d2*d3, RESHAPE(values(i,:,:,j), (/d2*d3/)), Npercen,                    &
4164              percentiles(i,1,1,j,:))
4165          END DO
4166        END DO
4167      ELSE IF (axis2(1) == 2 .AND. axis2(2) == 4) THEN
4168        DO i=1, d1
4169          DO j=1, d3
4170            CALL quantilesR_K(d2*d4, RESHAPE(values(i,:,j,:), (/d2*d4/)), Npercen,                    &
4171              percentiles(i,1,j,1,:))
4172          END DO
4173        END DO
4174      ELSE IF (axis2(1) == 3 .AND. axis2(2) == 4) THEN
4175        DO i=1, d1
4176          DO j=1, d2
4177            CALL quantilesR_K(d3*d4, RESHAPE(values(i,j,:,:), (/d3*d4/)), Npercen,                    &
4178              percentiles(i,j,1,1,:))
4179          END DO
4180        END DO
4181      ELSE
4182        WRITE(Naxs1,'(A1)')axis2(1)
4183        WRITE(Naxs2,'(A1)')axis2(2)
4184        msg="' rank 4 values can not compute percentiles using axis "//Naxs1// ', ' // Naxs2 // "' !!"
4185        CALL ErrMsg(msg, fname, -1)
4186      END IF
4187    ELSE IF (iichar == 2) THEN
4188      IF (axis2(1) == 1 .AND. axis2(2) == 2 .AND. axis3(3) == 3) THEN
4189        DO i=1, d4
4190          CALL quantilesR_K(d1*d2*d3, RESHAPE(values(:,:,:,i), (/d1*d2*d3/)), Npercen,                &
4191            percentiles(1,1,1,i,:))
4192        END DO
4193      ELSE IF (axis2(1) == 1 .AND. axis2(2) == 2 .AND. axis3(3) == 4) THEN
4194        DO i=1, d3
4195          CALL quantilesR_K(d1*d2*d4, RESHAPE(values(:,:,i,:), (/d1*d2*d4/)), Npercen,                &
4196            percentiles(1,1,i,1,:))
4197        END DO
4198      ELSE IF (axis2(1) == 1 .AND. axis2(2) == 3 .AND. axis3(3) == 4) THEN
4199        DO i=1, d2
4200          CALL quantilesR_K(d1*d3*d4, RESHAPE(values(:,i,:,:), (/d1*d3*d4/)), Npercen,                &
4201            percentiles(1,i,1,1,:))
4202        END DO
4203      ELSE IF (axis2(1) == 2 .AND. axis2(2) == 3 .AND. axis3(3) == 4) THEN
4204        DO i=1, d1
4205          CALL quantilesR_K(d2*d3*d4, RESHAPE(values(i,:,:,:), (/d2*d3*d4/)), Npercen,                &
4206            percentiles(i,1,1,1,:))
4207        END DO
4208      ELSE
4209        WRITE(Naxs1,'(A1)')axis3(1)
4210        WRITE(Naxs2,'(A1)')axis3(2)
4211        WRITE(Naxs3,'(A1)')axis3(2)
4212        msg="' rank 4 values can not compute percentiles using axis "// Naxs1 // ', ' // Naxs2 //     &
4213          ', ' // Naxs3 //"' !!"
4214        CALL ErrMsg(msg, fname, -1)
4215      END IF
4216    ELSE
4217      CALL quantilesR_K(d1*d2*d3*d4, RESHAPE(values, (/d1*d2*d3*d4/)), Npercen, percentiles(1,1,1,1,:))
4218    END IF
4219
4220  END SUBROUTINE percentiles_R_K4D
4221
4222  REAL(r_k) FUNCTION distanceRK(pointA, pointB)
4223  ! Function to provide the distance between two points
4224
4225    IMPLICIT NONE
4226
4227    REAL(r_k), DIMENSION(2), INTENT(in)                  :: pointA, pointB
4228
4229!!!!!!! Variables
4230! pointA, B: couple of points to compute the distance between them
4231
4232    fname = 'distanceRK'
4233
4234    distanceRK = SQRT( (pointB(1)-pointA(1))**2 + (pointB(2)-pointA(2))**2 )
4235
4236  END FUNCTION distanceRK
4237
4238  REAL(r_k) FUNCTION shoelace_area_polygon(Nvertex, poly)
4239  ! Computing the area of a polygon using sholace formula
4240  ! FROM: https://en.wikipedia.org/wiki/Shoelace_formula
4241
4242    IMPLICIT NONE
4243
4244      INTEGER, INTENT(in)                                :: Nvertex
4245      REAL(r_k), DIMENSION(Nvertex,2), INTENT(in)        :: poly
4246
4247! Local
4248      INTEGER                                            :: i
4249      REAL(r_k)                                          :: areapos, areaneg
4250
4251!!!!!!! Variables
4252! Nvertex: number of vertices of the polygon
4253! poly: coordinates of the vertex of the polygon (sorted)
4254
4255    fname = 'shoelace_area_polygon'
4256
4257    areapos = 0.
4258    areaneg = 0.
4259
4260    DO i=1, Nvertex-1
4261      areapos = areapos + poly(i,1)*poly(i+1,2)
4262      areaneg = areaneg + poly(i+1,1)*poly(i,2)
4263    END DO
4264
4265    areapos = areapos + poly(Nvertex,1)*poly(1,2)
4266    areaneg = areaneg + poly(1,1)*poly(Nvertex,2)
4267
4268    shoelace_area_polygon = 0.5*(areapos - areaneg)
4269
4270  END FUNCTION shoelace_area_polygon
4271
4272  SUBROUTINE intersection_2Dlines(lineA, lineB, intersect, ptintersect)
4273  ! Subroutine to provide the intersection point between two lines on the plane using Cramer's method
4274
4275    IMPLICIT NONE
4276
4277    REAL(r_k), DIMENSION(2,2), INTENT(in)                  :: lineA, lineB
4278    LOGICAL, INTENT(out)                                   :: intersect
4279    REAL(r_k), DIMENSION(2), INTENT(out)                   :: ptintersect
4280
4281! Local
4282    REAL(r_k), DIMENSION(2)                                :: segmentA, segmentB
4283    REAL(r_k)                                              :: a11, a12, a21, a22, z1, z2
4284    REAL(r_k)                                              :: det, detX, detY
4285    LOGICAL                                                :: axisAx, axisBx, axisAy, axisBy
4286
4287!!!!!!! Variables
4288! lineA: couple of coordinates for the line A
4289! lineB: couple of coordinates for the line B
4290! intersect: whether two lines intersect
4291! ptintersect: point of intersection [(0,0) if they do not intersect]
4292
4293    fname = 'intersection_2Dlines'
4294
4295    axisAx = .FALSE.
4296    axisAy = .FALSE.
4297    axisBx = .FALSE.
4298    axisBy = .FALSE.
4299    ! Setting segment parameters y = A + B*x
4300    IF (lineA(2,1) /= lineA(1,1)) THEN
4301      segmentA(2) = (lineA(2,2)-lineA(1,2))/(lineA(2,1)-lineA(1,1))
4302      ! This might be to ask too much... ?
4303      !IF ( (lineA(1,1)*segmentA(2) - lineA(1,2)) /= (lineA(2,1)*segmentA(2) - lineA(2,2)) ) THEN
4304      !  PRINT *,'A = y1 - x2*B = ', lineA(1,2) - lineA(1,1)*segmentA(2)
4305      !  PRINT *,'A = y2 - x2*B = ', lineA(2,2) - lineA(2,1)*segmentA(2)
4306      !  msg = 'Wrong calculation of parameter A, for lineA'
4307      !  CALL ErrMSg(msg, fname, -1)
4308      !END IF
4309      segmentA(1) = lineA(1,2) - lineA(1,1)*segmentA(2)
4310      a11 = segmentA(2)
4311      a12 = -oneRK
4312      z1 = -segmentA(1)
4313      IF (lineA(2,2) == lineA(1,2)) axisAx = .TRUE.
4314    ELSE
4315      ! lineA || y-axis
4316      axisAy = .TRUE.
4317    END IF
4318
4319    IF (lineB(2,1) /= lineB(1,1)) THEN
4320      segmentB(2) = (lineB(2,2)-lineB(1,2))/(lineB(2,1)-lineB(1,1))
4321      ! This might be to ask too much... ?
4322      !IF ( (lineB(1,1)*segmentB(2) - lineB(1,2)) /= (lineB(2,1)*segmentB(2) - lineB(2,2)) ) THEN
4323      !  PRINT *,'A = x1*B -y1 = ', lineB(1,1)*segmentB(2) - lineB(1,2)
4324      !  PRINT *,'A = x2*B -y2 = ', lineB(2,1)*segmentB(2) - lineB(2,2)
4325      !  msg = 'Wrong calculation of parameter A, for lineB'
4326      !  CALL ErrMSg(msg, fname, -1)
4327      !END IF
4328      segmentB(1) = lineB(1,2) - lineB(1,1)*segmentB(2)
4329      a21 = segmentB(2)
4330      a22 = -oneRK
4331      z2 = -segmentB(1)
4332      IF (lineB(2,2) == lineB(1,2)) axisBx = .TRUE.
4333    ELSE
4334      ! lineB || y-axis
4335      axisBy = .TRUE.
4336    END IF
4337    ! Cramer's method
4338    ! a11 = B1; a12 = -1
4339    ! a21 = B2; a22 = -1
4340    ! z1 = -A1
4341    ! z2 = -A2
4342    ! (a11 a12)(x) (z1)
4343    ! (a21 a22)(y) (z2)
4344    ! -------- ------ ----- ---- --- -- -
4345    ! det = (a11*a22-a12*a21)
4346    ! detX = (z1*a22-z2*a21)
4347    ! detY = (a11*z1-a12*z2)
4348    ! ptintercept = (detX/det, detY/det)
4349
4350    ! Cases when some of the lines are parallel to any given axis
4351!    PRINT *,'          axisAx', axisAx, 'axisAy', axisAy, 'axisBx', axisBx, 'axisBy', axisBy
4352    IF (axisAx .OR. axisAy .OR. axisBx .OR. axisBy) THEN
4353      IF (axisAx) THEN
4354        IF (axisBy) THEN
4355          intersect = .TRUE.
4356          ptintersect(1) = lineB(1,1)
4357          ptintersect(2) = lineA(1,2)
4358        ELSE
4359          intersect = .TRUE.
4360          ptintersect(1) = (lineA(1,2)-segmentB(1))/segmentB(2)
4361          ptintersect(2) = lineA(1,2)
4362        END IF
4363      END IF
4364      IF (axisAy) THEN
4365        IF (axisBy) THEN
4366          intersect = .TRUE.
4367          ptintersect(1) = lineA(1,1)
4368          ptintersect(2) = lineB(1,2)
4369        ELSE
4370          intersect = .TRUE.
4371          ptintersect(1) = lineA(1,1)
4372          ptintersect(2) = segmentB(1) + lineA(1,1)*segmentB(2)
4373        END IF
4374      END IF
4375      IF (axisBx) THEN
4376        IF (axisAy) THEN
4377          intersect = .TRUE.
4378          ptintersect(1) = lineA(1,1)
4379          ptintersect(2) = lineB(1,2)
4380        ELSE
4381          intersect = .TRUE.
4382          ptintersect(1) = (lineB(1,2)-segmentA(1))/segmentA(2)
4383          ptintersect(2) = lineB(1,2)
4384        END IF
4385      END IF
4386      IF (axisBy) THEN
4387        IF (axisAx) THEN
4388          intersect = .TRUE.
4389          ptintersect(1) = lineB(1,1)
4390          ptintersect(2) = lineA(1,2)
4391        ELSE
4392          intersect = .TRUE.
4393          ptintersect(1) = lineB(1,1)
4394          ptintersect(2) = segmentA(1) + lineB(1,1)*segmentA(2)
4395        END IF
4396      END IF
4397    ELSE
4398      det = (a11*a22-a12*a21)
4399      ! Parallel lines !
4400      IF (det == zeroRK) THEN
4401        intersect = .FALSE.
4402        ptintersect = zeroRK
4403      ELSE
4404        intersect = .TRUE.
4405        detX = (z1*a22-z2*a12)
4406        detY = (a11*z2-a21*z1)
4407
4408        ptintersect(1) = detX/det
4409        ptintersect(2) = detY/det
4410      END IF
4411    END IF
4412
4413  END SUBROUTINE intersection_2Dlines
4414
4415!refs:
4416!https://www.mathopenref.com/heronsformula.html
4417!https://math.stackexchange.com/questions/1406340/intersect-area-of-two-polygons-in-cartesian-plan
4418!http://www.cap-lore.com/MathPhys/IP/
4419!http://www.cap-lore.com/MathPhys/IP/IL.html
4420!https://www.element84.com/blog/determining-the-winding-of-a-polygon-given-as-a-set-of-ordered-points
4421!https://stackoverflow.com/questions/1165647/how-to-determine-if-a-list-of-polygon-points-are-in-clockwise-order
4422!https://en.wikipedia.org/wiki/Shoelace_formula
4423!https://en.wikipedia.org/wiki/Winding_number
4424!https://en.wikipedia.org/wiki/Simple_polygon
4425!https://en.wikipedia.org/wiki/Polygon#Properties
4426!https://en.wikipedia.org/wiki/Convex_polygon
4427!https://en.wikipedia.org/wiki/Jordan_curve_theorem
4428!https://www.sangakoo.com/ca/temes/metode-de-cramer
4429!https://www.geogebra.org/m/pw4QHFYT
4430
4431  SUBROUTINE intersectfaces(faceA, faceB, intersect, intersectpt)
4432  ! Subroutine to provide if two faces of two polygons intersect
4433  ! AFTER: http://www.cap-lore.com/MathPhys/IP/IL.html
4434  !   A: faceA(1,:)
4435  !   B: faceA(2,:)
4436  !   C: faceB(1,:)
4437  !   D: faceB(2,:)
4438
4439    IMPLICIT NONE
4440
4441    REAL(r_k), DIMENSION(2,2), INTENT(in)                :: faceA, faceB
4442    INTEGER, INTENT(out)                                 :: intersect
4443    REAL(r_k), DIMENSION(2), INTENT(out)                 :: intersectpt
4444
4445! Local
4446    REAL(r_k)                                            :: Axmin, Aymin, Axmax, Aymax
4447    REAL(r_k)                                            :: Bxmin, Bymin, Bxmax, Bymax
4448    REAL(r_k)                                            :: areaABD, areaACD, areaBDC, areaDAB
4449    REAL(r_k), DIMENSION(3,2)                            :: triangle
4450    LOGICAL                                              :: Lintersect
4451
4452!!!!!!! Variables
4453! faceA/B: coordinates of faces A and B to determine if they intersect
4454! intersect: integer to say if they intersect (0, no-intersect, +/-1 intersect)
4455! intersectpt: point where faces intersect [(0,0) otherwise]
4456
4457    fname = 'intersectfaces'
4458
4459!    PRINT *,'     ' // TRIM(fname) // ' ________'
4460!    PRINT *,'            faceA:', faceA(1,:), ';',faceA(2,:)
4461!    PRINT *,'            faceB:', faceB(1,:), ';',faceB(2,:)
4462
4463    Axmin = MINVAL(faceA(:,1))
4464    Axmax = MAXVAL(faceA(:,1))
4465    Aymin = MINVAL(faceA(:,2))
4466    Aymax = MAXVAL(faceA(:,2))
4467    Bxmin = MINVAL(faceB(:,1))
4468    Bxmax = MAXVAL(faceB(:,1))
4469    Bymin = MINVAL(faceB(:,2))
4470    Bymax = MAXVAL(faceB(:,2))
4471
4472    ! No intersection
4473    IF ( (Axmax <= Bxmin) .OR. (Axmin >= Bxmax) .OR. (Aymax <= Bymin) .OR. (Aymin >= Bymax) ) THEN
4474      intersect = 0
4475      intersectpt = zeroRK
4476    ELSE
4477      ! Triangle ABD
4478      triangle(1,:) = faceA(1,:)
4479      triangle(2,:) = faceA(2,:)
4480      triangle(3,:) = faceB(2,:)
4481      areaABD = shoelace_area_polygon(3, triangle)
4482 
4483      ! Triangle ACD
4484      triangle(1,:) = faceA(1,:)
4485      triangle(2,:) = faceB(1,:)
4486      triangle(3,:) = faceB(2,:)
4487      areaACD = shoelace_area_polygon(3, triangle)
4488
4489      ! Triangle BDC
4490      triangle(1,:) = faceA(2,:)
4491      triangle(2,:) = faceB(2,:)
4492      triangle(3,:) = faceB(1,:)
4493      areaBDC = shoelace_area_polygon(3, triangle)
4494
4495      ! Triangle DAB
4496      triangle(1,:) = faceB(2,:)
4497      triangle(2,:) = faceA(1,:)
4498      triangle(3,:) = faceA(2,:)
4499      areaDAB = shoelace_area_polygon(3, triangle)
4500
4501      IF (areaABD>zeroRK .AND. areaACD>zeroRK .AND. areaBDC>zeroRK .AND. areaDAB>zeroRK) THEN
4502        intersect = INT(ABS(areaABD)/areaABD)
4503        CALL intersection_2Dlines(faceA, faceB, Lintersect, intersectpt)
4504      ELSE IF (areaABD<zeroRK .AND. areaACD<zeroRK .AND. areaBDC<zeroRK .AND. areaDAB<zeroRK) THEN
4505        intersect = INT(ABS(areaABD)/areaABD)
4506        CALL intersection_2Dlines(faceA, faceB, Lintersect, intersectpt)
4507      ELSE
4508        intersect = 0
4509        intersectpt = zeroRK
4510      END IF
4511!      PRINT *,'     intersect faces: areaABD',areaABD, 'areaACD', areaACD, 'areaBDC',areaBDC, 'areaDAB',areaDAB, 'prod', &
4512!        areaABD*areaACD*areaBDC*areaDAB, 'L:', areaABD*areaACD*areaBDC*areaDAB > zeroRK, 'I', intersect
4513
4514    END IF
4515
4516  END SUBROUTINE intersectfaces
4517
4518  LOGICAL FUNCTION poly_has_point(Nvertex, polygon, point)
4519  ! Function to determine if a polygon has already a given point as one of its vertex
4520
4521    IMPLICIT NONE
4522
4523    INTEGER, INTENT(in)                                  :: Nvertex
4524    REAL(r_k), DIMENSION(Nvertex,2), INTENT(in)          :: polygon
4525    REAL(r_k), DIMENSION(2), INTENT(in)                  :: point
4526
4527! Local
4528    INTEGER                                              :: iv
4529    REAL(r_k), DIMENSION(2)                              :: diff
4530
4531!!!!!!! Vertrex
4532! Nvertex: number of vertexs of the polygon
4533! polygon: vertexs of the polygon
4534! point: point to look for its ownership into the polygon
4535
4536    fname = 'poly_has_point'
4537
4538    poly_has_point = .FALSE.
4539    DO iv=1, Nvertex
4540      diff = polygon(iv,:)-point
4541      IF ( (diff(1) == zeroRK) .AND. (diff(2) == zeroRK)) THEN
4542        poly_has_point = .TRUE.
4543        EXIT
4544      END IF
4545    END DO
4546
4547  END FUNCTION poly_has_point
4548
4549  SUBROUTINE join_polygon(NvertexA, NvertexB, NvertexAB, polyA, polyB, Ncoinvertex, coinpoly)
4550  ! Subroutine to join two polygons
4551  ! AFTER: http://www.cap-lore.com/MathPhys/IP/ and http://www.cap-lore.com/MathPhys/IP/IL.html
4552
4553    IMPLICIT NONE
4554
4555    INTEGER, INTENT(in)                                  :: NvertexA, NvertexB, NvertexAB
4556    REAL(r_k), DIMENSION(NvertexA,2), INTENT(in)         :: polyA
4557    REAL(r_k), DIMENSION(NvertexB,2), INTENT(in)         :: polyB
4558    INTEGER, INTENT(out)                                 :: Ncoinvertex
4559    REAL(r_k), DIMENSION(NvertexAB,2), INTENT(out)        :: coinpoly
4560
4561! Local
4562    INTEGER                                              :: iA, iB, icoin, ii
4563    REAL(r_k), DIMENSION(2,2)                            :: face1, face2
4564    INTEGER                                              :: intersct
4565    REAL(r_k), DIMENSION(2)                              :: ptintersct
4566
4567
4568!!!!!!! variables
4569! NvertexA: number of vertexs polygon A
4570! NvertexB: number of vertexs polygon B
4571! polyA: pairs of coordinates for the polygon A (clockwise)
4572! polyB: pairs of coordinates for the polygon B (clockwise)
4573! Ncoinvertex: number of vertexes for the coincident polygon
4574! coinpoly: pairs of coordinates for the coincident polygon (clockwise)
4575
4576    fname = 'join_polygon'
4577
4578    icoin = 0
4579    coinpoly = 0.
4580
4581    ! First, include that vertex which do not lay within any polygon
4582    DO iA=1, NvertexA
4583      !PRINT *, '  iA:', iA, ':', polyA(iA,:), point_inside(polyA(iA,:), NvertexB, polyB)
4584      IF (.NOT. point_inside(polyA(iA,:), NvertexB, polyB)) THEN
4585        icoin = icoin + 1
4586        coinpoly(icoin,:) = polyA(iA,:)
4587      END IF
4588    END DO
4589
4590    DO iB=1, NvertexB
4591      !PRINT *, '  iB:', iB, ':', polyB(iB,:), point_inside(polyB(iB,:), NvertexA, polyA)
4592      IF (.NOT. point_inside(polyB(iB,:), NvertexA, polyA)) THEN
4593        icoin = icoin + 1
4594        coinpoly(icoin,:) = polyB(iB,:)
4595      END IF
4596    END DO
4597
4598    DO iA=1, NvertexA
4599      ! Getting couple of vertexs from polyA and polyB
4600      IF (iA /= NvertexA) THEN
4601        face1(1,:) = polyA(iA,:)
4602        face1(2,:) = polyA(iA+1,:)
4603      ELSE
4604        face1(1,:) = polyA(iA,:)
4605        face1(2,:) = polyA(1,:)
4606      END IF
4607      DO iB=1, NvertexB
4608        IF (iB /= NvertexB) THEN
4609          face2(1,:) = polyB(iB,:)
4610          face2(2,:) = polyB(iB+1,:)
4611        ELSE
4612          face2(1,:) = polyB(iB,:)
4613          face2(2,:) = polyB(1,:)
4614        END IF
4615       
4616        ! Compute areas of the four possible triangles. Introduce the coincident vertexs not included
4617        CALL intersectfaces(face1, face2, intersct, ptintersct)
4618        !PRINT *,iA,':',face1(1,:),';',face1(2,:), '=', iB, face2(1,:),';',face2(2,:), '<>', intersct,':', ptintersct
4619        IF (intersct == 1) THEN
4620          IF (.NOT.poly_has_point(icoin,coinpoly(1:icoin,:),ptintersct) ) THEN
4621            icoin = icoin + 1
4622            coinpoly(icoin,:) = ptintersct
4623          END IF
4624        ELSE IF (intersct == -1) THEN
4625          IF (.NOT.poly_has_point(icoin,coinpoly(1:icoin,:),ptintersct) ) THEN
4626            icoin = icoin + 1
4627            coinpoly(icoin,:) = ptintersct
4628          END IF
4629        END IF
4630
4631      END DO
4632    END DO
4633    Ncoinvertex = icoin
4634
4635  END SUBROUTINE join_polygon
4636
4637  SUBROUTINE sort_polygon(Nvertex, polygon, sense, Nnewvertex, newpoly)
4638  ! Subroutine to sort a polygon using its center as average of the coordinates and remove duplicates
4639  !    Should be used the centroid instead, but by now let do it simple
4640  !    https://en.wikipedia.org/wiki/Centroid
4641
4642
4643    IMPLICIT NONE
4644
4645    INTEGER, INTENT(in)                                  :: Nvertex, sense
4646    REAL(r_k), DIMENSION(Nvertex,2), INTENT(in)          :: polygon
4647    INTEGER, INTENT(out)                                 :: Nnewvertex
4648    REAL(r_k), DIMENSION(Nvertex,2), INTENT(out)         :: newpoly
4649
4650! Local
4651    INTEGER                                              :: iv, j
4652    REAL(r_k)                                            :: vang
4653    REAL(r_k), DIMENSION(2)                              :: center
4654    REAL(r_k), DIMENSION(Nvertex)                        :: angles
4655    REAL(r_k), DIMENSION(Nvertex,2)                      :: sortpoly
4656
4657!!!!!!! Variables
4658! Nvertex: number of vertices
4659! polygon: coordinates of the vertices of the polygon
4660! sense: sens of sorting thepolygon (1: clockwise, -1: anti-clockwise)
4661! sortpoly: sorted polygon
4662! Nnewvertex: number of vertices new polygon
4663! newpoly: sorted and duplicate removed polygon
4664
4665    fname = 'sort_polygon'
4666
4667    ! To be substituted by centroid calculation (which requires already sorted vetexs...)
4668    center(1) = SUM(polygon(:,1))/Nvertex
4669    center(2) = SUM(polygon(:,2))/Nvertex
4670
4671    DO iv=1, Nvertex
4672      angles(iv) = ATAN2(polygon(iv,2)-center(2),polygon(iv,1)-center(1))
4673    END DO
4674    CALL sortR_K(angles, Nvertex)
4675
4676    sortpoly = zeroRK
4677    DO iv=1, Nvertex
4678      DO j=1, Nvertex
4679        vang = ATAN2(polygon(j,2)-center(2), polygon(j,1)-center(1))
4680        IF (angles(iv) == vang) THEN
4681          IF (sense == -1) THEN
4682            sortpoly(iv,:) = polygon(j,:)
4683          ELSE
4684            sortpoly(Nvertex-iv+1,:) = polygon(j,:)
4685          END IF
4686          EXIT
4687        END IF
4688      END DO
4689    END DO
4690
4691    newpoly(1,:) = sortpoly(1,:)
4692    j = 1
4693    DO iv=2, Nvertex
4694      IF (.NOT.poly_has_point(j,newpoly(1:j,:),sortpoly(iv,:)) ) THEN
4695        j = j+1
4696        newpoly(j,:) = sortpoly(iv,:)
4697      END IF
4698    END DO
4699    Nnewvertex = j
4700
4701  END SUBROUTINE sort_polygon
4702
4703  LOGICAL FUNCTION point_inside(point, Nvertex, polygon)
4704  ! Function to determine if a given point is inside a polygon providing its sorted vertices
4705  ! FROM: https://en.wikipedia.org/wiki/Point_in_polygon
4706
4707    IMPLICIT NONE
4708
4709    REAL(r_k), DIMENSION(2), INTENT(in)                  :: point
4710    INTEGER, INTENT(in)                                  :: Nvertex
4711    REAL(r_k), DIMENSION(Nvertex,2), INTENT(in)          :: polygon
4712
4713    ! Local
4714    INTEGER                                              :: iv, Nintersect
4715    INTEGER                                              :: cross
4716    REAL(r_k)                                            :: xmin
4717    REAL(r_k), DIMENSION(2)                              :: crosspoint
4718    REAL(r_k), DIMENSION(2,2)                            :: face1, face2
4719    REAL(r_k), DIMENSION(Nvertex)                        :: abovebelow
4720
4721!!!!!!! Variables
4722! point: point to look for
4723! Nvertrex: number of vertices of a polygon
4724! polygon: vertices of a polygon
4725
4726    fname = 'point_inside'
4727
4728    xmin = MINVAL(polygon(:,1))
4729
4730    ! Looking for the intersection with the ray
4731    Nintersect = 0
4732    face1(1,:) = (/ xmin-0.5, point(2) /)
4733    face1(2,:) = (/ point(1), point(2) /)
4734
4735    DO iv = 1, Nvertex
4736      IF (iv /= Nvertex) THEN
4737        face2(1,:) = polygon(iv,:)
4738        face2(2,:) = polygon(iv+1,:)
4739      ELSE
4740        face2(1,:) = polygon(iv,:)
4741        face2(2,:) = polygon(1,:)
4742      END IF
4743      CALL intersectfaces(face1, face2, cross, crosspoint)
4744      IF (cross /= 0) THEN
4745        Nintersect = Nintersect + 1
4746        abovebelow(Nintersect) = iv
4747      END IF
4748    END DO
4749
4750    IF (MOD(Nintersect,2) == 0) THEN
4751      point_inside = .FALSE.
4752    ELSE
4753      point_inside = .TRUE.
4754    END IF
4755
4756  END FUNCTION point_inside
4757
4758  LOGICAL FUNCTION point_in_face(pt, Nvertex, poly)
4759  ! Function to determine if a given point is on a face of a polygon
4760
4761    IMPLICIT NONE
4762
4763    REAL(r_k), DIMENSION(2), INTENT(in)                  :: pt
4764    INTEGER, INTENT(in)                                  :: Nvertex
4765    REAL(r_k), DIMENSION(Nvertex,2), INTENT(in)          :: poly
4766! Local
4767    INTEGER                                              :: iv
4768    REAL(r_k)                                            :: ix, ex, iy, ey, tmpv
4769    REAL(r_k)                                            :: dx, dy, A, B
4770
4771!!!!!!! Variables
4772! pt: point to look for
4773! Nvertex: Number of vertices of the polygon
4774! poly: polygon
4775    fname = 'point_in_face'
4776
4777    point_in_face = .FALSE.
4778    DO iv=1, Nvertex
4779      IF (iv < Nvertex) THEN
4780        ix = poly(iv,1)
4781        ex = poly(iv+1,1)
4782        iy = poly(iv,2)
4783        ey = poly(iv+1,2)
4784      ELSE
4785        ix = poly(iv,1)
4786        ex = poly(1,1)
4787        iy = poly(iv,2)
4788        ey = poly(1,2)
4789      END IF   
4790      dx = ex - ix
4791      dy = ey - iy
4792
4793      IF (dx == zeroRK) THEN
4794        IF (pt(1) == ix) THEN
4795          IF ( (iy < ey) .AND. (pt(2) >= iy) .AND. pt(2) <= ey) THEN
4796            point_in_face = .TRUE.
4797            EXIT
4798          ELSE IF ( (iy > ey) .AND. (pt(2) >= ey) .AND. pt(2) <= iy) THEN
4799            point_in_face = .TRUE.
4800            EXIT
4801          END IF
4802        END IF
4803      ELSE
4804        IF (dy == zeroRK) THEN
4805          IF (pt(2) == iy) THEN
4806            IF ((ix < ex) .AND. (pt(1) >= ix) .AND. pt(1) <= ex) THEN
4807              point_in_face = .TRUE.
4808              EXIT           
4809            ELSE IF ((ix > ex) .AND. (pt(1) >= ex) .AND. pt(1) <= ix) THEN
4810              point_in_face = .TRUE.
4811              EXIT
4812            END IF
4813          END IF
4814        ELSE
4815          A = iy
4816          B = (ey-iy)/(ex-ix)
4817          IF (A+B*(pt(1)-ix) == pt(2)) THEN
4818            point_in_face = .TRUE.
4819            EXIT
4820          END IF
4821        END IF
4822      END IF
4823    END DO
4824
4825  END FUNCTION point_in_face
4826
4827  SUBROUTINE coincident_polygon(NvertexA, NvertexB, NvertexAB, polyA, polyB, Ncoinvertex, coinpoly)
4828  ! Subroutine to provide the intersection polygon between two polygons
4829  ! AFTER: http://www.cap-lore.com/MathPhys/IP/ and http://www.cap-lore.com/MathPhys/IP/IL.html
4830
4831    IMPLICIT NONE
4832
4833    INTEGER, INTENT(in)                                  :: NvertexA, NvertexB, NvertexAB
4834    REAL(r_k), DIMENSION(NvertexA,2), INTENT(in)         :: polyA
4835    REAL(r_k), DIMENSION(NvertexB,2), INTENT(in)         :: polyB
4836    INTEGER, INTENT(out)                                 :: Ncoinvertex
4837    REAL(r_k), DIMENSION(NvertexAB,2), INTENT(out)       :: coinpoly
4838
4839! Local
4840    INTEGER                                              :: iA, iB, icoin, ii
4841    REAL(r_k), DIMENSION(2,2)                            :: face1, face2
4842    INTEGER                                              :: intersct
4843    REAL(r_k), DIMENSION(2)                              :: ptintersct
4844
4845!!!!!!! variables
4846! NvertexA: number of vertexs polygon A
4847! NvertexB: number of vertexs polygon B
4848! polyA: pairs of coordinates for the polygon A (clockwise)
4849! polyB: pairs of coordinates for the polygon B (clockwise)
4850! Ncoinvertex: number of vertexes for the coincident polygon
4851! coinpoly: pairs of coordinates for the coincident polygon (clockwise)
4852
4853    fname = 'coincident_polygon'
4854
4855    icoin = 0
4856    coinpoly = 0.
4857    ! First, include that vertex which lay within any polygon
4858    DO iA=1, NvertexA
4859      IF (point_inside(polyA(iA,:), NvertexB, polyB)) THEN
4860        icoin = icoin + 1
4861        coinpoly(icoin,:) = polyA(iA,:)
4862      END IF
4863      IF (point_in_face(polyA(iA,:), NvertexB, polyB)) THEN
4864        icoin = icoin + 1
4865        coinpoly(icoin,:) = polyA(iA,:)
4866      END IF
4867    END DO
4868
4869    DO iB=1, NvertexB
4870      IF (point_inside(polyB(iB,:), NvertexA, polyA)) THEN
4871        icoin = icoin + 1
4872        coinpoly(icoin,:) = polyB(iB,:)
4873      END IF
4874      IF (point_in_face(polyB(iB,:), NvertexA, polyA)) THEN
4875        icoin = icoin + 1
4876        coinpoly(icoin,:) = polyB(iB,:)
4877      END IF
4878    END DO
4879
4880    ! Look interesections
4881    DO iA=1, NvertexA
4882      ! Getting couple of vertexs from polyA and polyB
4883      IF (iA /= NvertexA) THEN
4884        face1(1,:) = polyA(iA,:)
4885        face1(2,:) = polyA(iA+1,:)
4886      ELSE
4887        face1(1,:) = polyA(iA,:)
4888        face1(2,:) = polyA(1,:)
4889      END IF
4890      DO iB=1, NvertexB
4891        IF (iB /= NvertexB) THEN
4892          face2(1,:) = polyB(iB,:)
4893          face2(2,:) = polyB(iB+1,:)
4894        ELSE
4895          face2(1,:) = polyB(iB,:)
4896          face2(2,:) = polyB(1,:)
4897        END IF
4898       
4899        ! Compute areas of the four possible triangles. Introduce the coincident vertexs not included
4900        CALL intersectfaces(face1, face2, intersct, ptintersct)
4901        !PRINT *,iA,':',face1(1,:),';',face1(2,:), '=', iB, face2(1,:),';',face2(2,:), '<>', intersct,':', ptintersct
4902        IF ((intersct /= 0) .AND. (.NOT.poly_has_point(icoin,coinpoly(1:icoin,:),ptintersct)) ) THEN
4903          icoin = icoin + 1
4904          coinpoly(icoin,:) = ptintersct
4905        END IF
4906
4907      END DO
4908    END DO
4909    Ncoinvertex = icoin
4910
4911  END SUBROUTINE coincident_polygon
4912
4913  SUBROUTINE grid_within_polygon(NvertexA, polygonA, dx, dy, dxy, xCvals, yCvals, Nvertexmax, xBvals, &
4914    yBvals, Ngridsin, gridsin)
4915  ! Subroutine to determine which grid cells from a matrix lay inside a polygon
4916
4917    IMPLICIT NONE
4918
4919    INTEGER, INTENT(in)                                  :: NvertexA, dx, dy, dxy, Nvertexmax
4920    REAL(r_k), DIMENSION(NvertexA,2), INTENT(in)         :: polygonA
4921    REAL(r_k), DIMENSION(dx,dy), INTENT(in)              :: xCvals, yCvals
4922    REAL(r_k), DIMENSION(dx,dy,Nvertexmax), INTENT(in)   :: xBvals, yBvals
4923    INTEGER, INTENT(out)                                 :: Ngridsin
4924    INTEGER, DIMENSION(dxy,2), INTENT(out)               :: gridsin
4925
4926! Local
4927    INTEGER                                              :: ix, iy, iv
4928    REAL(r_k), DIMENSION(2)                              :: centergrid, vertex
4929    LOGICAL, DIMENSION(dx,dy)                            :: within
4930
4931!!!!!!! Variables
4932! NvertexA: Number of vertices of the polygin to find the grids
4933! polygonA: ordered vertices of the polygon
4934! dx, dy: shape of the matrix with the grid points
4935! xCvals, yCvals: coordinates of the center of the grid cells
4936! Nvertexmax: Maximum number of vertices of the grid cells
4937! xBvals, yBvals: coordinates of th vertices of the grid cells (-99999 for no vertex)
4938! Ngridsin: number of grids with some extension within the polygon
4939! gridsin: grids within the polygin
4940! percentages: percentages of area of each of the grids within the polygon
4941
4942    fname = 'spacepercen_within_reg'
4943
4944    Ngridsin = 0
4945    gridsin = 0
4946    within = .FALSE.
4947    DO ix = 1, dx
4948      DO iy = 1, dy
4949        IF (.NOT.within(ix,iy)) THEN
4950          centergrid = (/ xCvals(ix,iy), yCvals(ix,iy) /)
4951          ! By grid center
4952          IF (point_inside(centergrid, NvertexA, polygonA)) THEN
4953            Ngridsin = Ngridsin + 1
4954            ! Getting coordinates
4955            gridsin(Ngridsin,1) = ix
4956            gridsin(Ngridsin,2) = iy
4957            within(ix,iy) = .TRUE.
4958            CYCLE
4959          END IF
4960
4961          ! Getting grid vertices
4962          DO iv=1, Nvertexmax
4963            IF (.NOT.within(ix,iy)) THEN
4964              IF (xBvals(ix,iy,iv) /= fillvalI) THEN
4965                vertex = (/ xBvals(ix,iy,iv), yBvals(ix,iy,iv) /)
4966                IF (point_inside(vertex, NvertexA, polygonA)) THEN
4967                  Ngridsin = Ngridsin + 1
4968                  ! Getting coordinates
4969                  gridsin(Ngridsin,1) = ix
4970                  gridsin(Ngridsin,2) = iy
4971                  within(ix,iy) = .TRUE.
4972                  CYCLE
4973                END IF
4974              END IF
4975            END IF
4976          END DO
4977
4978        END IF
4979      END DO
4980    END DO
4981
4982  END SUBROUTINE grid_within_polygon
4983
4984  SUBROUTINE spacepercen_within_reg(NvertexA, polygonA, dx, dy, Nvertexmax, xBvals, yBvals,           &
4985    Ngridsin, gridsin, strict, percentages)
4986  ! Subroutine to compute the percentage of a series of grid cells which are encompassed by a polygon
4987  ! NOTE: Assuming coordinates on the plane with rectilinar, distance preserved and perpendicular x
4988  !   and y axes.
4989
4990    IMPLICIT NONE
4991
4992    INTEGER, INTENT(in)                                  :: NvertexA, dx, dy, Nvertexmax
4993    REAL(r_k), DIMENSION(NvertexA,2), INTENT(in)         :: polygonA
4994    REAL(r_k), DIMENSION(dx,dy,Nvertexmax), INTENT(in)   :: xBvals, yBvals
4995    INTEGER, INTENT(in)                                  :: Ngridsin
4996    INTEGER, DIMENSION(Ngridsin,2), INTENT(in)           :: gridsin
4997    LOGICAL, INTENT(in)                                  :: strict
4998    REAL(r_k), DIMENSION(Ngridsin), INTENT(out)          :: percentages
4999
5000! Local
5001   INTEGER                                               :: ig, iv, ix, iy
5002   INTEGER                                               :: Nvertex, NvertexAgrid, Ncoin, Nsort
5003   CHARACTER(len=20)                                     :: DS
5004   REAL(r_k)                                             :: areapoly, areagpoly, totarea, totpercent
5005   REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                :: vertexgrid, icoinpoly, coinpoly,          &
5006     sortpoly, poly
5007
5008!!!!!!! Variables
5009! NvertexA: Number of vertices of the polygin to find the grids
5010! polygonA: ordered vertices of the polygon
5011! dx, dy: shape of the matrix with the grid points
5012! xCvals, yCvals: coordinates of the center of the grid cells
5013! Nvertexmax: Maximum number of vertices of the grid cells
5014! xBvals, yBvals: coordinates of th vertices of the grid cells (-99999 for no vertex)
5015! Ngridsin: number of grids with some extension within the polygon
5016! gridsin: grids within the polygon
5017! strict: give an error if the area of the polygon is not fully covered
5018! percentages: percentages of area of each of the grids within the polygon
5019
5020    fname = 'spacepercen_within_reg'
5021
5022    percentages = zeroRK
5023    totpercent = zeroRK
5024    totarea = zeroRK
5025
5026    areapoly = shoelace_area_polygon(NvertexA, polygonA)
5027
5028    DO ig = 1, Ngridsin
5029      ix = gridsin(ig,1)
5030      iy = gridsin(ig,2)
5031
5032      ! Getting grid vertices
5033      Nvertex = 0
5034      DO iv=1, Nvertexmax
5035        IF (xBvals(ix,iy,iv) /= fillvalI) THEN
5036          Nvertex = Nvertex + 1
5037        END IF
5038      END DO
5039      IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5040      ALLOCATE(vertexgrid(Nvertex,2))
5041      vertexgrid(:,1) = xBvals(ix,iy,1:Nvertex)
5042      vertexgrid(:,2) = yBvals(ix,iy,1:Nvertex)
5043
5044      ! Getting common vertices
5045      NvertexAgrid = NvertexA*Nvertex*2
5046      IF (ALLOCATED(icoinpoly)) DEALLOCATE(icoinpoly)
5047      ALLOCATE(icoinpoly(NvertexAgrid,2))
5048      CALL coincident_polygon(NvertexA, Nvertex, NvertexAgrid, polygonA, vertexgrid, Ncoin, icoinpoly)
5049
5050      IF (ALLOCATED(coinpoly)) DEALLOCATE(coinpoly)
5051      ALLOCATE(coinpoly(Ncoin,2))
5052      DO iv=1, Ncoin
5053        coinpoly(iv,:) = icoinpoly(iv,:)
5054      END DO
5055
5056      IF (ALLOCATED(sortpoly)) DEALLOCATE(sortpoly)
5057      ALLOCATE(sortpoly(Ncoin,2))
5058      CALL sort_polygon(Ncoin, coinpoly, 1, Nsort, sortpoly)
5059
5060      IF (ALLOCATED(poly)) DEALLOCATE(poly)
5061      ALLOCATE(poly(Nsort,2))
5062      DO iv=1, Nsort
5063        poly(iv,:) = sortpoly(iv,:)
5064      END DO
5065
5066      areagpoly = shoelace_area_polygon(Nsort, poly)
5067      IF (INT(LOG10(EPSILON(totpercent))) < 12) THEN
5068        totarea = totarea + ABS(areagpoly)
5069        percentages(ig) = ABS(areagpoly / areapoly)
5070! f2py does not like it!
5071!      ELSE
5072!        totarea = totarea + DABS(areagpoly)
5073!        percentages(ig) = DABS(areagpoly / areapoly)
5074      END IF
5075      totpercent = totpercent + percentages(ig)
5076    END DO
5077
5078    IF (INT(LOG10(EPSILON(totpercent))) < 12) THEN
5079      IF (strict .AND. ABS(totpercent - oneRK) > epsilonRK) THEN
5080        PRINT *, 'totarea:', totarea, ' area polygon:', areapoly
5081        PRINT *, 'totpercent:', totpercent, ' oneRK:', oneRK, ' diff:', totpercent - oneRK
5082        WRITE(DS,'(F20.8)')ABS(totpercent - oneRK)
5083        msg = 'sum of all grid space percentages does not cover (' // TRIM(DS) // ') all polygon'
5084        CALL ErrMsg(msg, fname, -1)
5085      END IF
5086    ELSE
5087! f2py does not like it!
5088!      IF (strict .AND. ABS(totpercent - oneRK) > epsilonRK) THEN
5089!        PRINT *, 'totarea:', totarea, ' area polygon:', areapoly
5090!        PRINT *, 'totpercent:', totpercent, ' oneRK:', oneRK, ' diff:', totpercent - oneRK
5091!        WRITE(DS,'(F20.16)')ABS(totpercent - oneRK)
5092!        msg = 'sum of all grid space percentages does not cover (' // TRIM(DS) // ') all polygon'
5093!        CALL ErrMsg(msg, fname, -1)
5094!      END IF
5095    END IF
5096
5097    IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5098    IF (ALLOCATED(icoinpoly)) DEALLOCATE(icoinpoly)
5099    IF (ALLOCATED(coinpoly)) DEALLOCATE(coinpoly)
5100    IF (ALLOCATED(sortpoly)) DEALLOCATE(sortpoly)
5101    IF (ALLOCATED(poly)) DEALLOCATE(poly)
5102
5103  END SUBROUTINE spacepercen_within_reg
5104
5105  SUBROUTINE grid_spacepercen_within_reg(NvertexA, polygonA, dx, dy, Nvertexmax, xBvals, yBvals,      &
5106    Ngridsin, gridsin, strict, gridspace, percentages)
5107  ! Subroutine to compute the percentage of grid space of a series of grid cells which are encompassed
5108  !   by a polygon
5109  ! NOTE: Assuming coordinates on the plane with rectilinar, distance preserved and perpendicular x
5110  !   and y axes.
5111
5112    IMPLICIT NONE
5113
5114    INTEGER, INTENT(in)                                  :: NvertexA, dx, dy, Nvertexmax
5115    REAL(r_k), DIMENSION(NvertexA,2), INTENT(in)         :: polygonA
5116    REAL(r_k), DIMENSION(dx,dy,Nvertexmax), INTENT(in)   :: xBvals, yBvals
5117    INTEGER, INTENT(in)                                  :: Ngridsin
5118    INTEGER, DIMENSION(Ngridsin,2), INTENT(in)           :: gridsin
5119    LOGICAL, INTENT(in)                                  :: strict
5120    REAL(r_k), DIMENSION(Ngridsin), INTENT(out)          :: gridspace, percentages
5121
5122! Local
5123   INTEGER                                               :: ig, iv, ix, iy
5124   INTEGER                                               :: Nvertex, NvertexAgrid, Ncoin, Nsort
5125   CHARACTER(len=20)                                     :: DS
5126   REAL(r_k)                                             :: areapoly, areagpoly
5127   REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                :: vertexgrid, icoinpoly, coinpoly,          &
5128     sortpoly, poly
5129
5130!!!!!!! Variables
5131! NvertexA: Number of vertices of the polygon to find the grids
5132! polygonA: ordered vertices of the polygon
5133! dx, dy: shape of the matrix with the grid points
5134! xCvals, yCvals: coordinates of the center of the grid cells
5135! Nvertexmax: Maximum number of vertices of the grid cells
5136! xBvals, yBvals: coordinates of th vertices of the grid cells (-99999 for no vertex)
5137! Ngridsin: number of grids with some extension within the polygon
5138! gridsin: grids within the polygon
5139! strict: give an error if the area of the polygon is not fully covered
5140! gridspace: area of each of the grids
5141! percentages: percentages of grid area of each of the grids within the polygon
5142
5143    fname = 'grid_spacepercen_within_reg'
5144
5145    gridspace = zeroRK
5146    percentages = zeroRK
5147
5148    DO ig = 1, Ngridsin
5149      ix = gridsin(ig,1)
5150      iy = gridsin(ig,2)
5151
5152     ! Getting grid vertices
5153      Nvertex = 0
5154      DO iv=1, Nvertexmax
5155        IF (xBvals(ix,iy,iv) /= fillvalI) THEN
5156          Nvertex = Nvertex + 1
5157        END IF
5158      END DO
5159      IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5160      ALLOCATE(vertexgrid(Nvertex,2))
5161      vertexgrid(:,1) = xBvals(ix,iy,1:Nvertex)
5162      vertexgrid(:,2) = yBvals(ix,iy,1:Nvertex)
5163      areapoly = shoelace_area_polygon(Nvertex, vertexgrid)
5164
5165      ! Getting common vertices
5166      NvertexAgrid = NvertexA*Nvertex*2
5167      IF (ALLOCATED(icoinpoly)) DEALLOCATE(icoinpoly)
5168      ALLOCATE(icoinpoly(NvertexAgrid,2))
5169      CALL coincident_polygon(NvertexA, Nvertex, NvertexAgrid, polygonA, vertexgrid, Ncoin, icoinpoly)
5170
5171      IF (ALLOCATED(coinpoly)) DEALLOCATE(coinpoly)
5172      ALLOCATE(coinpoly(Ncoin,2))
5173      DO iv=1, Ncoin
5174        coinpoly(iv,:) = icoinpoly(iv,:)
5175      END DO
5176
5177      IF (ALLOCATED(sortpoly)) DEALLOCATE(sortpoly)
5178      ALLOCATE(sortpoly(Ncoin,2))
5179      CALL sort_polygon(Ncoin, coinpoly, 1, Nsort, sortpoly)
5180
5181      IF (ALLOCATED(poly)) DEALLOCATE(poly)
5182      ALLOCATE(poly(Nsort,2))
5183      DO iv=1, Nsort
5184        poly(iv,:) = sortpoly(iv,:)
5185      END DO
5186
5187      areagpoly = shoelace_area_polygon(Nsort, poly)
5188      gridspace(ig) = ABS(areapoly)
5189      percentages(ig) = ABS(areagpoly / areapoly)
5190    END DO
5191
5192    IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5193    IF (ALLOCATED(icoinpoly)) DEALLOCATE(icoinpoly)
5194    IF (ALLOCATED(coinpoly)) DEALLOCATE(coinpoly)
5195    IF (ALLOCATED(sortpoly)) DEALLOCATE(sortpoly)
5196    IF (ALLOCATED(poly)) DEALLOCATE(poly)
5197
5198  END SUBROUTINE grid_spacepercen_within_reg
5199
5200  SUBROUTINE grid_spacepercen_within_reg_providing_polys(NvertexA, polygonA, dx, dy, Nvertexmax,      &
5201    xBvals, yBvals, Ngridsin, gridsin, strict, Nmaxver2, Ncoinpoly, ccoinpoly, gridspace, percentages)
5202  ! Subroutine to compute the percentage of grid space of a series of grid cells which are encompassed
5203  !   by a polygon providing coordinates of the resultant polygons
5204  ! NOTE: Assuming coordinates on the plane with rectilinar, distance preserved and perpendicular x
5205  !   and y axes.
5206
5207    IMPLICIT NONE
5208
5209    INTEGER, INTENT(in)                                  :: NvertexA, dx, dy, Nvertexmax, Nmaxver2
5210    REAL(r_k), DIMENSION(NvertexA,2), INTENT(in)         :: polygonA
5211    REAL(r_k), DIMENSION(dx,dy,Nvertexmax), INTENT(in)   :: xBvals, yBvals
5212    INTEGER, INTENT(in)                                  :: Ngridsin
5213    INTEGER, DIMENSION(Ngridsin,2), INTENT(in)           :: gridsin
5214    LOGICAL, INTENT(in)                                  :: strict
5215    INTEGER, DIMENSION(Ngridsin), INTENT(out)            :: Ncoinpoly
5216    REAL(r_k), DIMENSION(Ngridsin,Nmaxver2,2),                                                        &
5217      INTENT(out)                                        :: ccoinpoly
5218    REAL(r_k), DIMENSION(Ngridsin), INTENT(out)          :: gridspace, percentages
5219
5220! Local
5221   INTEGER                                               :: ig, iv, ix, iy
5222   INTEGER                                               :: Nvertex, NvertexAgrid, Ncoin, Nsort
5223   CHARACTER(len=20)                                     :: DS
5224   REAL(r_k)                                             :: areapoly, areagpoly
5225   REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                :: vertexgrid, icoinpoly, coinpoly,          &
5226     sortpoly, poly
5227
5228!!!!!!! Variables
5229! NvertexA: Number of vertices of the polygon to find the grids
5230! polygonA: ordered vertices of the polygon
5231! dx, dy: shape of the matrix with the grid points
5232! xCvals, yCvals: coordinates of the center of the grid cells
5233! Nvertexmax: Maximum number of vertices of the grid cells
5234! xBvals, yBvals: coordinates of th vertices of the grid cells (-99999 for no vertex)
5235! Ngridsin: number of grids with some extension within the polygon
5236! gridsin: grids within the polygon
5237! strict: give an error if the area of the polygon is not fully covered
5238! Nmaxver2: maximum possible number of vertices of the coincident polygon
5239! Ncoinpoly: number of vertices of the coincident polygon
5240! coinpoly: coordinates of the vertices of the coincident polygon
5241! gridspace: area of each of the grids
5242! percentages: percentages of grid area of each of the grids within the polygon
5243
5244    fname = 'grid_spacepercen_within_reg_providing_polys'
5245
5246    gridspace = zeroRK
5247    percentages = zeroRK
5248
5249    DO ig = 1, Ngridsin
5250      ix = gridsin(ig,1)
5251      iy = gridsin(ig,2)
5252
5253     ! Getting grid vertices
5254      Nvertex = 0
5255      DO iv=1, Nvertexmax
5256        IF (xBvals(ix,iy,iv) /= fillvalI) THEN
5257          Nvertex = Nvertex + 1
5258        END IF
5259      END DO
5260      IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5261      ALLOCATE(vertexgrid(Nvertex,2))
5262      vertexgrid(:,1) = xBvals(ix,iy,1:Nvertex)
5263      vertexgrid(:,2) = yBvals(ix,iy,1:Nvertex)
5264      areapoly = shoelace_area_polygon(Nvertex, vertexgrid)
5265
5266      ! Getting common vertices
5267      NvertexAgrid = NvertexA*Nvertex*2
5268      IF (ALLOCATED(icoinpoly)) DEALLOCATE(icoinpoly)
5269      ALLOCATE(icoinpoly(NvertexAgrid,2))
5270      CALL coincident_polygon(NvertexA, Nvertex, NvertexAgrid, polygonA, vertexgrid, Ncoin, icoinpoly)
5271
5272      IF (ALLOCATED(coinpoly)) DEALLOCATE(coinpoly)
5273      ALLOCATE(coinpoly(Ncoin,2))
5274      DO iv=1, Ncoin
5275        coinpoly(iv,:) = icoinpoly(iv,:)
5276      END DO
5277
5278      IF (ALLOCATED(sortpoly)) DEALLOCATE(sortpoly)
5279      ALLOCATE(sortpoly(Ncoin,2))
5280      CALL sort_polygon(Ncoin, coinpoly, 1, Nsort, sortpoly)
5281
5282      IF (ALLOCATED(poly)) DEALLOCATE(poly)
5283      ALLOCATE(poly(Nsort,2))
5284      DO iv=1, Nsort
5285        poly(iv,:) = sortpoly(iv,:)
5286      END DO
5287
5288      areagpoly = shoelace_area_polygon(Nsort, poly)
5289      Ncoinpoly(ig)= Nsort
5290      ccoinpoly(ig,:,:) = poly(:,:)
5291      gridspace(ig) = ABS(areapoly)
5292      percentages(ig) = ABS(areagpoly / areapoly)
5293    END DO
5294
5295    IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5296    IF (ALLOCATED(icoinpoly)) DEALLOCATE(icoinpoly)
5297    IF (ALLOCATED(coinpoly)) DEALLOCATE(coinpoly)
5298    IF (ALLOCATED(sortpoly)) DEALLOCATE(sortpoly)
5299    IF (ALLOCATED(poly)) DEALLOCATE(poly)
5300
5301  END SUBROUTINE grid_spacepercen_within_reg_providing_polys
5302
5303  SUBROUTINE spacepercen(xCAvals, yCAvals, xBAvals, yBAvals, xCBvals, yCBvals, xBBvals, yBBvals,      &
5304    dxA, dyA, NAvertexmax, dxB, dyB, dxyB, NBvertexmax, strict, Ngridsin, gridsin, areas, percentages)
5305  ! Subroutine to compute the space-percentages of a series of grid cells (B) into another series of
5306  !   grid-cells (A)
5307  ! NOTE: Assuming coordinates on the plane with rectilinar, distance preserved and perpendicular x
5308  !   and y axes.
5309
5310    IMPLICIT NONE
5311
5312    INTEGER, INTENT(in)                                  :: dxA, dyA, NAvertexmax
5313    INTEGER, INTENT(in)                                  :: dxB, dyB, NBvertexmax, dxyB
5314    REAL(r_k), DIMENSION(dxA,dyA), INTENT(in)            :: xCAvals, yCAvals
5315    REAL(r_k), DIMENSION(dxB,dyB), INTENT(in)            :: xCBvals, yCBvals
5316    REAL(r_k), DIMENSION(dxA,dyA,NAvertexmax), INTENT(in):: xBAvals, yBAvals
5317    REAL(r_k), DIMENSION(dxB,dyB,NBvertexmax), INTENT(in):: xBBvals, yBBvals
5318    LOGICAL, INTENT(in)                                  :: strict
5319    INTEGER, DIMENSION(dxA,dyA), INTENT(out)             :: Ngridsin
5320    INTEGER, DIMENSION(dxA,dyA,dxyB,2), INTENT(out)      :: gridsin
5321    REAL(r_k), DIMENSION(dxA,dyA), INTENT(out)           :: areas
5322    REAL(r_k), DIMENSION(dxA,dyA,dxyB), INTENT(out)      :: percentages
5323
5324! Local
5325   INTEGER                                               :: iv, ix, iy
5326   INTEGER                                               :: Nvertex
5327   INTEGER, ALLOCATABLE, DIMENSION(:,:)                  :: poinsin
5328   CHARACTER(len=20)                                     :: IS
5329   REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                :: vertexgrid
5330
5331!!!!!!! Variables
5332! dxA, dyA: shape of the matrix with the grid points A
5333! xCAvals, yCAvals: coordinates of the center of the grid cells A
5334! NAvertexmax: Maximum number of vertices of the grid cells A
5335! xBAvals, yBAvals: coordinates of th vertices of the grid cells A (-99999 for no vertex)
5336! dxB, dyB: shape of the matrix with the grid points B
5337! xCBvals, yCBvals: coordinates of the center of the grid cells B
5338! NBvertexmax: Maximum number of vertices of the grid cells B
5339! xBBvals, yBBvals: coordinates of th vertices of the grid cells B (-99999 for no vertex)
5340! strict: give an error if the area of the polygon is not fully covered
5341! Ngridsin: number of grids from grid B with some extension within the grid cell A
5342! gridsin: indices of B grids within the grids of A
5343! areas: areas of the polygons
5344! percentages: percentages of area of cells B of each of the grids within the grid cell A
5345
5346    fname = 'spacepercen'
5347
5348    DO ix = 1, dxA
5349      DO iy = 1, dyA
5350
5351        ! Getting grid vertices
5352        Nvertex = 0
5353        DO iv=1, NAvertexmax
5354          IF (xBAvals(ix,iy,iv) /= fillval64) THEN
5355           Nvertex = Nvertex + 1
5356          END IF
5357        END DO
5358        IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5359        ALLOCATE(vertexgrid(Nvertex,2))
5360        vertexgrid(:,1) = xBAvals(ix,iy,1:Nvertex)
5361        vertexgrid(:,2) = yBAvals(ix,iy,1:Nvertex)
5362 
5363        CALL grid_within_polygon(Nvertex, vertexgrid, dxB, dyB, dxB*dyB, xCBvals, yCBvals,            &
5364          NBvertexmax, xBBvals, yBBvals, Ngridsin(ix,iy), gridsin(ix,iy,:,:))
5365   
5366        IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin)
5367        ALLOCATE(poinsin(Ngridsin(ix,iy),2))
5368
5369        DO iv=1, Ngridsin(ix,iy)
5370          poinsin(iv,1) = gridsin(ix,iy,iv,1)
5371          poinsin(iv,2) = gridsin(ix,iy,iv,2)
5372        END DO
5373
5374        areas(ix,iy) = shoelace_area_polygon(Nvertex, vertexgrid)
5375        CALL spacepercen_within_reg(Nvertex, vertexgrid, dxB, dyB, NBvertexmax, xBBvals, yBBvals,     &
5376          Ngridsin(ix,iy), poinsin, strict, percentages(ix,iy,:))
5377
5378      END DO
5379    END DO
5380
5381    IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5382    IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin)
5383
5384  END SUBROUTINE spacepercen
5385
5386  SUBROUTINE grid_spacepercen(xCAvals, yCAvals, xBAvals, yBAvals, xCBvals, yCBvals, xBBvals, yBBvals, &
5387    dxA, dyA, NAvertexmax, dxB, dyB, dxyB, NBvertexmax, strict, Ngridsin, gridsin,  areas2D, areas,   &
5388    percentages)
5389  ! Subroutine to compute the space-percentages of a series of grid cells (B) which lay inside another
5390  !   series of grid-cells (A) porviding coincident polygons
5391  ! NOTE: Assuming coordinates on the plane with rectilinar, distance preserved and perpendicular x
5392  !   and y axes.
5393
5394    IMPLICIT NONE
5395
5396    INTEGER, INTENT(in)                                  :: dxA, dyA, NAvertexmax
5397    INTEGER, INTENT(in)                                  :: dxB, dyB, NBvertexmax, dxyB
5398    REAL(r_k), DIMENSION(dxA,dyA), INTENT(in)            :: xCAvals, yCAvals
5399    REAL(r_k), DIMENSION(dxB,dyB), INTENT(in)            :: xCBvals, yCBvals
5400    REAL(r_k), DIMENSION(dxA,dyA,NAvertexmax), INTENT(in):: xBAvals, yBAvals
5401    REAL(r_k), DIMENSION(dxB,dyB,NBvertexmax), INTENT(in):: xBBvals, yBBvals
5402    LOGICAL, INTENT(in)                                  :: strict
5403    INTEGER, DIMENSION(dxA,dyA), INTENT(out)             :: Ngridsin
5404    INTEGER, DIMENSION(dxA,dyA,dxyB,2), INTENT(out)      :: gridsin
5405    REAL(r_k), DIMENSION(dxB,dyB), INTENT(out)           :: areas2D
5406    REAL(r_k), DIMENSION(dxA,dyA,dxyB), INTENT(out)      :: areas,percentages
5407
5408! Local
5409   INTEGER                                               :: iv, ix, iy
5410   INTEGER                                               :: Nvertex, Nptin
5411   INTEGER, ALLOCATABLE, DIMENSION(:,:)                  :: poinsin
5412   CHARACTER(len=20)                                     :: IS
5413   REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                :: vertexgrid
5414
5415!!!!!!! Variables
5416! dxA, dyA: shape of the matrix with the grid points A
5417! xCAvals, yCAvals: coordinates of the center of the grid cells A
5418! NAvertexmax: Maximum number of vertices of the grid cells A
5419! xBAvals, yBAvals: coordinates of th vertices of the grid cells A (-99999 for no vertex)
5420! dxB, dyB: shape of the matrix with the grid points B
5421! xCBvals, yCBvals: coordinates of the center of the grid cells B
5422! NBvertexmax: Maximum number of vertices of the grid cells B
5423! xBBvals, yBBvals: coordinates of th vertices of the grid cells B (-99999 for no vertex)
5424! strict: give an error if the area of the polygon is not fully covered
5425! Ngridsin: number of grids from grid B with some extension within the grid cell A
5426! gridsin: indices of B grids within the grids of A
5427! areas2D: areas of the grids as 2D matrix in the original shape
5428! areas: areas of cells B of each of the grids inside the grid cell A
5429! percentages: percentages of area of cells B of each of the grids inside the grid cell A
5430
5431    fname = 'grid_spacepercen'
5432
5433    areas2D = zeroRK
5434    areas = zeroRK
5435    percentages = zeroRK
5436
5437    DO ix = 1, dxA
5438      DO iy = 1, dyA
5439
5440        ! Getting grid vertices
5441        Nvertex = 0
5442        DO iv=1, NAvertexmax
5443          IF (xBAvals(ix,iy,iv) /= fillval64) THEN
5444           Nvertex = Nvertex + 1
5445          END IF
5446        END DO
5447        IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5448        ALLOCATE(vertexgrid(Nvertex,2))
5449        vertexgrid(:,1) = xBAvals(ix,iy,1:Nvertex)
5450        vertexgrid(:,2) = yBAvals(ix,iy,1:Nvertex)
5451 
5452        CALL grid_within_polygon(Nvertex, vertexgrid, dxB, dyB, dxB*dyB, xCBvals, yCBvals,            &
5453          NBvertexmax, xBBvals, yBBvals, Ngridsin(ix,iy), gridsin(ix,iy,1:dxyB,:))
5454   
5455        IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin)
5456        ALLOCATE(poinsin(Ngridsin(ix,iy),2))
5457
5458        DO iv=1, Ngridsin(ix,iy)
5459          poinsin(iv,1) = gridsin(ix,iy,iv,1)
5460          poinsin(iv,2) = gridsin(ix,iy,iv,2)
5461        END DO
5462
5463        Nptin = Ngridsin(ix,iy)
5464        CALL grid_spacepercen_within_reg(Nvertex, vertexgrid, dxB, dyB, NBvertexmax, xBBvals,        &
5465          yBBvals, Ngridsin(ix,iy), poinsin, strict, areas(ix,iy,1:Nptin), percentages(ix,iy,1:Nptin))
5466
5467        ! Filling areas
5468        DO iv = 1, Ngridsin(ix,iy)
5469          IF (areas2D(poinsin(iv,1), poinsin(iv,2)) == zeroRK) THEN
5470            areas2D(poinsin(iv,1), poinsin(iv,2)) = areas(ix,iy,iv)
5471          END IF
5472        END DO
5473
5474      END DO
5475    END DO
5476
5477    IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5478    IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin)
5479
5480  END SUBROUTINE grid_spacepercen
5481
5482  SUBROUTINE grid_spacepercen_providing_polys(xCAvals, yCAvals, xBAvals, yBAvals, xCBvals, yCBvals,   &
5483    xBBvals, yBBvals, dxA, dyA, NAvertexmax, dxB, dyB, dxyB, NBvertexmax, strict, Nmaxvercoin,        &
5484    Nvercoinpolys, vercoinpolys, Ngridsin, gridsin,  areas, percentages)
5485  ! Subroutine to compute the space-percentages of a series of grid cells (B) which lay inside another
5486  !   series of grid-cells (A) providing coincident polygons
5487  ! NOTE: Assuming coordinates on the plane with rectilinar, distance preserved and perpendicular x
5488  !   and y axes.
5489
5490    IMPLICIT NONE
5491
5492    INTEGER, INTENT(in)                                  :: dxA, dyA, NAvertexmax
5493    INTEGER, INTENT(in)                                  :: dxB, dyB, NBvertexmax, dxyB
5494    INTEGER, INTENT(in)                                  :: Nmaxvercoin
5495    REAL(r_k), DIMENSION(dxA,dyA), INTENT(in)            :: xCAvals, yCAvals
5496    REAL(r_k), DIMENSION(dxB,dyB), INTENT(in)            :: xCBvals, yCBvals
5497    REAL(r_k), DIMENSION(dxA,dyA,NAvertexmax), INTENT(in):: xBAvals, yBAvals
5498    REAL(r_k), DIMENSION(dxB,dyB,NBvertexmax), INTENT(in):: xBBvals, yBBvals
5499    LOGICAL, INTENT(in)                                  :: strict
5500    INTEGER, DIMENSION(dxA,dyA,dxyB,Nmaxvercoin),                                                     &
5501      INTENT(out)                                        :: Nvercoinpolys
5502    REAL(r_k), DIMENSION(dxA,dyA,dxyB,Nmaxvercoin,2),                                                 &
5503      INTENT(out)                                        :: vercoinpolys
5504    INTEGER, DIMENSION(dxA,dyA), INTENT(out)             :: Ngridsin
5505    INTEGER, DIMENSION(dxA,dyA,dxyB,2), INTENT(out)      :: gridsin
5506    REAL(r_k), DIMENSION(dxB,dyB), INTENT(out)           :: areas
5507    REAL(r_k), DIMENSION(dxA,dyA,dxyB), INTENT(out)      :: percentages
5508
5509! Local
5510   INTEGER                                               :: iv, ix, iy
5511   INTEGER                                               :: Nvertex
5512   INTEGER, ALLOCATABLE, DIMENSION(:,:)                  :: poinsin
5513   CHARACTER(len=20)                                     :: IS
5514   REAL(r_k), ALLOCATABLE, DIMENSION(:)                  :: pareas
5515   REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                :: vertexgrid
5516
5517!!!!!!! Variables
5518! dxA, dyA: shape of the matrix with the grid points A
5519! xCAvals, yCAvals: coordinates of the center of the grid cells A
5520! NAvertexmax: Maximum number of vertices of the grid cells A
5521! xBAvals, yBAvals: coordinates of th vertices of the grid cells A (-99999 for no vertex)
5522! dxB, dyB: shape of the matrix with the grid points B
5523! xCBvals, yCBvals: coordinates of the center of the grid cells B
5524! NBvertexmax: Maximum number of vertices of the grid cells B
5525! xBBvals, yBBvals: coordinates of th vertices of the grid cells B (-99999 for no vertex)
5526! strict: give an error if the area of the polygon is not fully covered
5527! Nvercoinpolys: number of vertices of the coincident polygon of each grid
5528! coinpolys: of vertices of the coincident polygon of each grid
5529! Ngridsin: number of grids from grid B with some extension within the grid cell A
5530! gridsin: indices of B grids within the grids of A
5531! areas: areas of the grids
5532! percentages: percentages of area of cells B of each of the grids inside the grid cell A
5533
5534    fname = 'grid_spacepercen_providing_polys'
5535
5536    areas = zeroRK
5537
5538    DO ix = 1, dxA
5539      DO iy = 1, dyA
5540
5541        ! Getting grid vertices
5542        Nvertex = 0
5543        DO iv=1, NAvertexmax
5544          IF (xBAvals(ix,iy,iv) /= fillval64) THEN
5545           Nvertex = Nvertex + 1
5546          END IF
5547        END DO
5548        IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5549        ALLOCATE(vertexgrid(Nvertex,2))
5550        vertexgrid(:,1) = xBAvals(ix,iy,1:Nvertex)
5551        vertexgrid(:,2) = yBAvals(ix,iy,1:Nvertex)
5552 
5553        CALL grid_within_polygon(Nvertex, vertexgrid, dxB, dyB, dxB*dyB, xCBvals, yCBvals,            &
5554          NBvertexmax, xBBvals, yBBvals, Ngridsin(ix,iy), gridsin(ix,iy,:,:))
5555   
5556        IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin)
5557        ALLOCATE(poinsin(Ngridsin(ix,iy),2))
5558        IF (ALLOCATED(pareas)) DEALLOCATE(pareas)
5559        ALLOCATE(pareas(Ngridsin(ix,iy)))
5560
5561        DO iv=1, Ngridsin(ix,iy)
5562          poinsin(iv,1) = gridsin(ix,iy,iv,1)
5563          poinsin(iv,2) = gridsin(ix,iy,iv,2)
5564        END DO
5565
5566        CALL grid_spacepercen_within_reg_providing_polys(Nvertex, vertexgrid, dxB, dyB, NBvertexmax, &
5567          xBBvals, yBBvals, Ngridsin(ix,iy), poinsin, strict, Nmaxvercoin, Nvercoinpolys(ix,iy,:,:), &
5568          vercoinpolys(ix,iy,:,:,:), pareas, percentages(ix,iy,:))
5569
5570        ! Filling areas
5571        DO iv = 1, Ngridsin(ix,iy)
5572          IF (areas(poinsin(iv,1), poinsin(iv,2)) == zeroRK) THEN
5573            areas(poinsin(iv,1), poinsin(iv,2)) = pareas(iv)
5574          END IF
5575        END DO
5576
5577      END DO
5578    END DO
5579
5580    IF (ALLOCATED(vertexgrid)) DEALLOCATE(vertexgrid)
5581    IF (ALLOCATED(pareas)) DEALLOCATE(pareas)
5582    IF (ALLOCATED(poinsin)) DEALLOCATE(poinsin)
5583
5584  END SUBROUTINE grid_spacepercen_providing_polys
5585
5586  SUBROUTINE unique_matrixRK2D(dx, dy, dxy, matrix2D, Nunique, unique)
5587  ! Subroutine to provide the unique values within a 2D RK matrix
5588
5589    IMPLICIT NONE
5590
5591    INTEGER, INTENT(in)                                  :: dx, dy, dxy
5592    REAL(r_k), DIMENSION(dx,dy), INTENT(in)              :: matrix2D
5593    INTEGER, INTENT(out)                                 :: Nunique
5594    REAL(r_k), DIMENSION(dxy), INTENT(out)               :: unique
5595
5596! Local
5597    INTEGER                                              :: ix, iy, iu, minvalv
5598    LOGICAL                                              :: single
5599    REAL(r_k), ALLOCATABLE, DIMENSION(:)                 :: uniques
5600
5601
5602!!!!!!! Variables
5603! dx, dy: dimensions of the matrix
5604! dxy: dx*dy, maximum possible amount of different values
5605! matrix2D: matgrix of values
5606! Nunique: amount of unique values
5607! unique: sorted from minimum to maximum vector with the unique values
5608
5609    fname = 'unique_matrixRK2D'
5610
5611    minvalv = MINVAL(matrix2D)
5612
5613    Nunique = 1
5614    unique(1) = minvalv
5615    DO ix= 1, dx
5616      DO iy= 1, dy
5617        single = .TRUE.
5618        DO iu = 1, Nunique
5619          IF (matrix2D(ix,iy) == unique(iu)) THEN
5620            single = .FALSE.
5621            EXIT
5622          END IF
5623        END DO
5624        IF (single) THEN
5625          Nunique = Nunique + 1
5626          unique(Nunique) = matrix2D(ix,iy)
5627        END IF
5628      END DO
5629    END DO
5630    IF (ALLOCATED(uniques)) DEALLOCATE(uniques)
5631    ALLOCATE(uniques(Nunique))
5632    uniques(1:Nunique) = unique(1:Nunique)
5633   
5634    CALL sortR_K(uniques(1:Nunique), Nunique)
5635    unique(1:Nunique) = uniques(1:Nunique)
5636
5637  END SUBROUTINE unique_matrixRK2D
5638
5639  SUBROUTINE spaceweightstats(varin, Ngridsin, gridsin, percentages, stats, varout, dxA, dyA, dxB,    &
5640    dyB, maxNgridsin, Lstats)
5641  ! Subroutine to compute an spatial statistics value from a matrix B into a matrix A using weights
5642
5643    IMPLICIT NONE
5644
5645    INTEGER, INTENT(in)                                  :: dxA, dyA, dxB, dyB, maxNgridsin, Lstats
5646    CHARACTER(len=*), INTENT(in)                         :: stats
5647    INTEGER, DIMENSION(dxA,dyA), INTENT(in)              :: Ngridsin
5648    INTEGER, DIMENSION(dxA,dyA,maxNgridsin,2), INTENT(in):: gridsin
5649    REAL(r_k), DIMENSION(dxB,dyB), INTENT(in)            :: varin
5650    REAL(r_k), DIMENSION(dxA,dyA,maxNgridsin), INTENT(in):: percentages
5651    REAL(r_k), DIMENSION(dxA,dyA,Lstats), INTENT(out)    :: varout
5652
5653! Local
5654    INTEGER                                              :: ix, iy, iv, ic, iu, ii, jj
5655    INTEGER                                              :: Ncounts
5656    CHARACTER(len=3)                                     :: val1S, val2S
5657    CHARACTER(len=30)                                    :: val3S
5658    REAL(r_k)                                            :: val1, val2
5659    REAL(r_k), DIMENSION(Lstats)                         :: icounts
5660
5661!!!!!!! Variables
5662! dxA, dyA: length of dimensions of matrix A
5663! dxB, dyB: length of dimensions of matrix B
5664! maxNgridsin: maximum number of grid points from B to be used to compute into a grid of matrix A
5665! Lstats: length of the dimension of the statistics
5666! varin: variable from matrix B to be used
5667! Ngridsin: number of grids from matrix B for each grid of matrix A
5668! gridsin: coordinates of grids of matrix B for each grid of matrix A
5669! percentages: weights as percentages of space of grid in matrix A covered by grid of matrix B
5670! stats: name of the spatial statistics to compute inside each grid of matrix A using values from
5671!     matrix B. Avaialbe ones:
5672!   'min': minimum value
5673!   'max': maximum value
5674!   'mean': space weighted mean value
5675!   'mean2': space weighted quadratic mean value
5676!   'stddev': space weighted standard deviation value
5677!   'count': percentage of the space of matrix A covered by each different value of matrix B
5678! varout: output statistical variable
5679
5680    fname = 'spaceweightstats'
5681
5682    ! Let's be efficvient?
5683    statn: SELECT CASE(TRIM(stats))
5684      CASE('min')
5685        varout = fillVal64
5686        DO ix=1, dxA
5687          DO iy=1, dyA
5688            DO iv=1, Ngridsin(ix,iy)
5689              ii = gridsin(ix,iy,iv,1)
5690              jj = gridsin(ix,iy,iv,2)
5691              IF (varin(ii,jj) < varout(ix,iy,Lstats)) varout(ix,iy,1) = varin(ii,jj)
5692            END DO
5693          END DO
5694        END DO
5695      CASE('max')
5696        varout = -fillVal64
5697        DO ix=1, dxA
5698          DO iy=1, dyA
5699            DO iv=1, Ngridsin(ix,iy)
5700              ii = gridsin(ix,iy,iv,1)
5701              jj = gridsin(ix,iy,iv,2)
5702              IF (varin(ii,jj) > varout(ix,iy,Lstats)) varout(ix,iy,1) = varin(ii,jj)
5703            END DO
5704          END DO
5705        END DO
5706      CASE('mean')
5707        varout = zeroRK
5708        DO ix=1, dxA
5709          DO iy=1, dyA
5710            DO iv=1, Ngridsin(ix,iy)
5711              ii = gridsin(ix,iy,iv,1)
5712              jj = gridsin(ix,iy,iv,2)
5713              varout(ix,iy,1) = varout(ix,iy,1) + varin(ii,jj)*percentages(ix,iy,iv)
5714            END DO
5715          END DO
5716        END DO
5717      CASE('mean2')
5718        varout = zeroRK
5719        DO ix=1, dxA
5720          DO iy=1, dyA
5721            DO iv=1, Ngridsin(ix,iy)
5722              ii = gridsin(ix,iy,iv,1)
5723              jj = gridsin(ix,iy,iv,2)
5724              varout(ix,iy,1) = varout(ix,iy,1) + percentages(ix,iy,iv)*(varin(ii,jj))**2
5725            END DO
5726            varout(ix,iy,1) = varout(ix,iy,1) / Ngridsin(ix,iy)
5727          END DO
5728        END DO
5729      CASE('stddev')
5730        varout = zeroRK
5731        DO ix=1, dxA
5732          DO iy=1, dyA
5733            val1 = zeroRK
5734            val2 = zeroRK
5735            DO iv=1, Ngridsin(ix,iy)
5736              ii = gridsin(ix,iy,iv,1)
5737              jj = gridsin(ix,iy,iv,2)
5738              val1 = val1 + varin(ii,jj)*percentages(ix,iy,iv)
5739              val2 = val2 + percentages(ix,iy,iv)*(varin(ii,jj))**2
5740            END DO
5741            varout(ix,iy,1) = SQRT(val2 - val1**2)
5742          END DO
5743        END DO
5744      CASE('count')
5745        CALL unique_matrixRK2D(dxB, dyB, dxB*dyB, varin, Ncounts, icounts)
5746        IF (Lstats /= Ncounts) THEN
5747          PRINT *,'  ' // TRIM(fname) // 'provided:', Lstats
5748          PRINT *,'  ' // TRIM(fname) // 'found:', Ncounts, ' :', icounts
5749          WRITE(val1S,'(I3)')Lstats
5750          WRITE(val2S,'(I3)')Ncounts
5751          msg = "for 'count' different amount of passed categories: " // TRIM(val1S) //               &
5752            ' and found ' // TRIM(val2S)
5753          CALL ErrMsg(msg, fname, -1)
5754        END IF
5755        varout = zeroRK
5756        DO ix=1, dxA
5757          DO iy=1, dyA
5758            DO iv=1, Ngridsin(ix,iy)
5759              ii = gridsin(ix,iy,iv,1)
5760              jj = gridsin(ix,iy,iv,2)
5761              ic = Index1DArrayR_K(icounts, Ncounts, varin(ii,jj))
5762              IF (ic == -1) THEN
5763                WRITE(val3S,'(f30.20)')varin(ii,jj)
5764                msg = "value '" // val3S // "' for 'count' not found"
5765                CALL ErrMSg(msg, fname, -1)
5766              ELSE
5767                varout(ix,iy,ic) = varout(ix,iy,ic) + percentages(ix,iy,iv)
5768              END IF
5769            END DO
5770          END DO
5771        END DO
5772      CASE DEFAULT
5773        msg = "statisitcs '" // TRIM(stats) // "' not ready !!" // CHAR(44) // " available ones: " // &
5774          "'min', 'max', 'mean', 'mean2', 'stddev', 'count'"
5775        CALL ErrMsg(msg, fname, -1)
5776    END SELECT statn
5777
5778  END SUBROUTINE spaceweightstats
5779
5780  SUBROUTINE multi_spaceweightstats_in1DRKno_slc3v3(varin, idv, Ngridsin, gridsin, percentages,       &
5781    varout, di1, ds1, ds2, ds3, maxNgridsin)
5782  ! Subroutine to compute an spatial statistics value from a 1D RK matrix without running one into a
5783  !   matrix of 3-variables slices of rank 3 using spatial weights
5784
5785    IMPLICIT NONE
5786
5787    INTEGER, INTENT(in)                                  :: di1, idv, ds1, ds2, ds3
5788    INTEGER, INTENT(in)                                  :: maxNgridsin
5789    INTEGER, DIMENSION(ds1,ds2,ds3), INTENT(in)          :: Ngridsin
5790    INTEGER, DIMENSION(ds1,ds2,ds3,maxNgridsin,2),                                                    &
5791      INTENT(in)                                         :: gridsin
5792    REAL(r_k), DIMENSION(di1), INTENT(in)                :: varin
5793    REAL(r_k), INTENT(in),                                                                            &
5794      DIMENSION(ds1,ds2,ds3,maxNgridsin)                 :: percentages
5795    REAL(r_k), DIMENSION(ds1,ds2,ds3,7), INTENT(out)     :: varout
5796
5797! Local
5798    INTEGER                                              :: i1, i2, i3, s1, s2, s3, iv
5799    INTEGER                                              :: ii3, ss1, ss2, ss3
5800    INTEGER                                              :: Ncounts, Nin
5801    INTEGER, DIMENSION(1)                                :: dmaxvarin
5802    CHARACTER(len=3)                                     :: val1S, val2S
5803    CHARACTER(len=30)                                    :: val3S
5804    REAL(r_k)                                            :: minv, maxv, meanv, mean2v, stdv, medv
5805    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: pin
5806    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: gin
5807    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: svin
5808    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: vin
5809
5810!!!!!!! Variables
5811! di1: length of dimensions of the 1D matrix of values
5812! ds[1-3]: length of dimensions of matrix with the slices
5813! maxNgridsin: maximum number of grid points from the 3D matrix in any slice
5814! varin: 1D RK variable to be used
5815! idv: which dimension of the sliced grids coincide with the dimension of 1D varin
5816! Ngridsin: number of grids from 3D RK matrix for each slice
5817! gridsin: coordinates of grids of the 3D RK matrix B to matrix of slices
5818! percentages: weights as percentages of space of 3D RK matrix for each slice
5819!!!!!
5820! Available spatial statistics to compute inside each slice using values from 3D RK matrix
5821!   'min': minimum value
5822!   'max': maximum value
5823!   'mean': space weighted mean value
5824!   'mean2': space weighted quadratic mean value
5825!   'stddev': space weighted standard deviation value
5826!   'median': median value
5827!   'count': percentage of the space of matrix A covered by each different value of matrix B
5828! varout: output statistical variable
5829
5830    fname = 'multi_spaceweightstats_in1DRKno_slc3v3'
5831
5832    varout = fillval64
5833
5834    ss1 = 8 + 1
5835    ss2 = 5 + 1
5836    ss3 = 3 + 1
5837    ii3 = 1 + 1
5838
5839    dmaxvarin = UBOUND(varin)
5840
5841    ! Let's be efficient?
5842    varout = fillVal64
5843    DO s1 =1, ds1
5844      DO s2 =1, ds2
5845        DO s3 =1, ds3
5846          Nin = Ngridsin(s1,s2,s3)
5847          ! Computing along d3
5848          IF (Nin > 1) THEN
5849            IF (ALLOCATED(gin)) DEALLOCATE(gin)
5850            ALLOCATE(gin(Nin,2))
5851            IF (ALLOCATED(pin)) DEALLOCATE(pin)
5852            ALLOCATE(pin(Nin))
5853            IF (ALLOCATED(vin)) DEALLOCATE(vin)
5854            ALLOCATE(vin(Nin))
5855            IF (ALLOCATED(svin)) DEALLOCATE(svin)
5856            ALLOCATE(svin(Nin))
5857            gin = gridsin(s1,s2,s3,1:Nin,:)
5858            pin = percentages(s1,s2,s3,1:Nin)
5859
5860            ! Getting the values
5861            DO iv=1, Nin
5862              i1 = gin(iv,idv)
5863              vin(iv) = varin(i1)
5864            END DO
5865            minv = fillVal64
5866            maxv = -fillVal64
5867            meanv = zeroRK
5868            mean2v = zeroRK
5869            stdv = zeroRK
5870            minv = MINVAL(vin)
5871            maxv = MAXVAL(vin)
5872            meanv = SUM(vin*pin)
5873            mean2v = SUM(vin**2*pin)
5874            DO iv=1,Nin
5875              stdv = stdv + ( (meanv - vin(iv))*pin(iv) )**2
5876            END DO
5877            stdv = SQRT(stdv)
5878            svin = vin(:)
5879            CALL SortR_K(svin, Nin)
5880            medv = svin(INT(Nin/2))
5881            varout(s1,s2,s3,1) = minv
5882            varout(s1,s2,s3,2) = maxv
5883            varout(s1,s2,s3,3) = meanv
5884            varout(s1,s2,s3,4) = mean2v
5885            varout(s1,s2,s3,5) = stdv
5886            varout(s1,s2,s3,6) = medv
5887            varout(s1,s2,s3,7) = Nin*1.
5888          ELSE
5889            i1 = gridsin(s1,s2,s3,1,idv)
5890            IF (i1 > 0 .AND. i1 <= dmaxvarin(1)) THEN
5891              varout(s1,s2,s3,1) = varin(i1)
5892              varout(s1,s2,s3,2) = varin(i1)
5893              varout(s1,s2,s3,3) = varin(i1)
5894              varout(s1,s2,s3,4) = varin(i1)*varin(i1)
5895              varout(s1,s2,s3,5) = zeroRK
5896              varout(s1,s2,s3,6) = varin(i1)
5897              varout(s1,s2,s3,7) = Nin*1.
5898            END IF
5899          END IF
5900        END DO
5901      END DO
5902    END DO
5903
5904    IF (ALLOCATED(gin)) DEALLOCATE(gin)
5905    IF (ALLOCATED(pin)) DEALLOCATE(pin)
5906    IF (ALLOCATED(vin)) DEALLOCATE(vin)
5907    IF (ALLOCATED(svin)) DEALLOCATE(svin)
5908   
5909    RETURN
5910
5911  END SUBROUTINE multi_spaceweightstats_in1DRKno_slc3v3
5912
5913  SUBROUTINE multi_spaceweightstats_in2DRKno_slc3v3(varin, Ngridsin, gridsin, percentages, varout,     &
5914    di1, di2, ds1, ds2, ds3, maxNgridsin)
5915  ! Subroutine to compute an spatial statistics value from a 2D RK matrix without running one into a
5916  !   matrix of 3-variables slices of rank 3 using spatial weights
5917
5918    IMPLICIT NONE
5919
5920    INTEGER, INTENT(in)                                  :: di1, di2, ds1, ds2, ds3
5921    INTEGER, INTENT(in)                                  :: maxNgridsin
5922    INTEGER, DIMENSION(ds1,ds2,ds3), INTENT(in)          :: Ngridsin
5923    INTEGER, DIMENSION(ds1,ds2,ds3,maxNgridsin,2),                                                    &
5924      INTENT(in)                                         :: gridsin
5925    REAL(r_k), DIMENSION(di1,di2), INTENT(in)            :: varin
5926    REAL(r_k), INTENT(in),                                                                            &
5927      DIMENSION(ds1,ds2,ds3,maxNgridsin)                 :: percentages
5928    REAL(r_k), DIMENSION(ds1,ds2,ds3,7), INTENT(out)     :: varout
5929
5930! Local
5931    INTEGER                                              :: i1, i2, i3, s1, s2, s3, iv
5932    INTEGER                                              :: ii3, ss1, ss2, ss3
5933    INTEGER                                              :: Ncounts, Nin
5934    CHARACTER(len=3)                                     :: val1S, val2S
5935    CHARACTER(len=30)                                    :: val3S
5936    REAL(r_k)                                            :: minv, maxv, meanv, mean2v, stdv, medv
5937    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: pin
5938    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: gin
5939    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: svin
5940    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: vin
5941
5942!!!!!!! Variables
5943! di1, di2: length of dimensions of the 2D matrix of values
5944! ds[1-3]: length of dimensions of matrix with the slices
5945! maxNgridsin: maximum number of grid points from the 3D matrix in any slice
5946! varin: 2D RK variable to be used
5947! Ngridsin: number of grids from 3D RK matrix for each slice
5948! gridsin: coordinates of grids of the 3D RK matrix B to matrix of slices
5949! percentages: weights as percentages of space of 3D RK matrix for each slice
5950!!!!!
5951! Available spatial statistics to compute inside each slice using values from 3D RK matrix
5952!   'min': minimum value
5953!   'max': maximum value
5954!   'mean': space weighted mean value
5955!   'mean2': space weighted quadratic mean value
5956!   'stddev': space weighted standard deviation value
5957!   'median': median value
5958!   'count': percentage of the space of matrix A covered by each different value of matrix B
5959! varout: output statistical variable
5960
5961    fname = 'multi_spaceweightstats_in2DRKno_slc3v3'
5962
5963    varout = fillval64
5964
5965    ss1 = 8 + 1
5966    ss2 = 5 + 1
5967    ss3 = 3 + 1
5968    ii3 = 1 + 1
5969
5970    ! Let's be efficient?
5971    varout = fillVal64
5972    DO s1 =1, ds1
5973      DO s2 =1, ds2
5974        DO s3 =1, ds3
5975          Nin = Ngridsin(s1,s2,s3)
5976          ! Computing along d3
5977          IF (Nin > 1) THEN
5978            IF (ALLOCATED(gin)) DEALLOCATE(gin)
5979            ALLOCATE(gin(Nin,2))
5980            IF (ALLOCATED(pin)) DEALLOCATE(pin)
5981            ALLOCATE(pin(Nin))
5982            IF (ALLOCATED(vin)) DEALLOCATE(vin)
5983            ALLOCATE(vin(Nin))
5984            IF (ALLOCATED(svin)) DEALLOCATE(svin)
5985            ALLOCATE(svin(Nin))
5986            gin = gridsin(s1,s2,s3,1:Nin,:)
5987            pin = percentages(s1,s2,s3,1:Nin)
5988
5989            ! Getting the values
5990            DO iv=1, Nin
5991              i1 = gin(iv,1)
5992              i2 = gin(iv,2)
5993              vin(iv) = varin(i1,i2)
5994            END DO
5995            minv = fillVal64
5996            maxv = -fillVal64
5997            meanv = zeroRK
5998            mean2v = zeroRK
5999            stdv = zeroRK
6000            minv = MINVAL(vin)
6001            maxv = MAXVAL(vin)
6002            meanv = SUM(vin*pin)
6003            mean2v = SUM(vin**2*pin)
6004            DO iv=1,Nin
6005              stdv = stdv + ( (meanv - vin(iv))*pin(iv) )**2
6006            END DO
6007            stdv = SQRT(stdv)
6008            svin = vin(:)
6009            CALL SortR_K(svin, Nin)
6010            medv = svin(INT(Nin/2))
6011            varout(s1,s2,s3,1) = minv
6012            varout(s1,s2,s3,2) = maxv
6013            varout(s1,s2,s3,3) = meanv
6014            varout(s1,s2,s3,4) = mean2v
6015            varout(s1,s2,s3,5) = stdv
6016            varout(s1,s2,s3,6) = medv
6017            varout(s1,s2,s3,7) = Nin*1.
6018          ELSE
6019            i1 = gridsin(s1,s2,s3,1,1)
6020            i2 = gridsin(s1,s2,s3,1,2)
6021            varout(s1,s2,s3,1) = varin(i1,i2)
6022            varout(s1,s2,s3,2) = varin(i1,i2)
6023            varout(s1,s2,s3,3) = varin(i1,i2)
6024            varout(s1,s2,s3,4) = varin(i1,i2)*varin(i1,i2)
6025            varout(s1,s2,s3,5) = zeroRK
6026            varout(s1,s2,s3,6) = varin(i1,i2)
6027            varout(s1,s2,s3,7) = Nin*1.
6028          END IF
6029        END DO
6030      END DO
6031    END DO
6032
6033    IF (ALLOCATED(gin)) DEALLOCATE(gin)
6034    IF (ALLOCATED(pin)) DEALLOCATE(pin)
6035    IF (ALLOCATED(vin)) DEALLOCATE(vin)
6036    IF (ALLOCATED(svin)) DEALLOCATE(svin)
6037   
6038    RETURN
6039
6040  END SUBROUTINE multi_spaceweightstats_in2DRKno_slc3v3
6041
6042  SUBROUTINE multi_spaceweightstats_in3DRK3_slc3v3(varin, Ngridsin, gridsin, percentages, varout,     &
6043    di1, di2, di3, ds1, ds2, ds3, maxNgridsin)
6044  ! Subroutine to compute an spatial statistics value from a 3D RK matrix using 3rd dimension as
6045  !   running one into a matrix of 3-variables slices of rank 3 using spatial weights
6046
6047    IMPLICIT NONE
6048
6049    INTEGER, INTENT(in)                                  :: di1, di2, di3, ds1, ds2, ds3
6050    INTEGER, INTENT(in)                                  :: maxNgridsin
6051    INTEGER, DIMENSION(ds1,ds2,ds3), INTENT(in)          :: Ngridsin
6052    INTEGER, DIMENSION(ds1,ds2,ds3,maxNgridsin,2),                                                    &
6053      INTENT(in)                                         :: gridsin
6054    REAL(r_k), DIMENSION(di1,di2,di3), INTENT(in)        :: varin
6055    REAL(r_k), INTENT(in),                                                                            &
6056      DIMENSION(ds1,ds2,ds3,maxNgridsin)                 :: percentages
6057    REAL(r_k), DIMENSION(ds1,ds2,ds3,di3,7), INTENT(out) :: varout
6058
6059! Local
6060    INTEGER                                              :: i1, i2, i3, s1, s2, s3, iv
6061    INTEGER                                              :: ii3, ss1, ss2, ss3
6062    INTEGER                                              :: Ncounts, Nin
6063    CHARACTER(len=3)                                     :: val1S, val2S
6064    CHARACTER(len=30)                                    :: val3S
6065    REAL(r_k)                                            :: minv, maxv, meanv, mean2v, stdv, medv
6066    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: pin
6067    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: gin
6068    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: svin
6069    REAL(r_k), DIMENSION(:,:), ALLOCATABLE               :: vin
6070
6071!!!!!!! Variables
6072! di1, di2, di3: length of dimensions of the 3D matrix of values
6073! ds[1-3]: length of dimensions of matrix with the slices
6074! maxNgridsin: maximum number of grid points from the 3D matrix in any slice
6075! varin: 3D RK variable to be used
6076! Ngridsin: number of grids from 3D RK matrix for each slice
6077! gridsin: coordinates of grids of the 3D RK matrix B to matrix of slices
6078! percentages: weights as percentages of space of 3D RK matrix for each slice
6079!!!!!
6080! Available spatial statistics to compute inside each slice using values from 3D RK matrix
6081!   'min': minimum value
6082!   'max': maximum value
6083!   'mean': space weighted mean value
6084!   'mean2': space weighted quadratic mean value
6085!   'stddev': space weighted standard deviation value
6086!   'median': median value
6087!   'count': percentage of the space of matrix A covered by each different value of matrix B
6088! varout: output statistical variable
6089
6090    fname = 'multi_spaceweightstats_in3DRK3_slc3v3'
6091
6092    varout = fillval64
6093
6094    ss1 = 8 + 1
6095    ss2 = 5 + 1
6096    ss3 = 3 + 1
6097    ii3 = 1 + 1
6098
6099    ! Let's be efficient?
6100    varout = fillVal64
6101    DO s1 =1, ds1
6102      DO s2 =1, ds2
6103        DO s3 =1, ds3
6104          Nin = Ngridsin(s1,s2,s3)
6105          ! Computing along d3
6106          IF (Nin > 1) THEN
6107            IF (ALLOCATED(gin)) DEALLOCATE(gin)
6108            ALLOCATE(gin(Nin,2))
6109            IF (ALLOCATED(pin)) DEALLOCATE(pin)
6110            ALLOCATE(pin(Nin))
6111            IF (ALLOCATED(vin)) DEALLOCATE(vin)
6112            ALLOCATE(vin(Nin,di3))
6113            IF (ALLOCATED(svin)) DEALLOCATE(svin)
6114            ALLOCATE(svin(Nin))
6115            gin = gridsin(s1,s2,s3,1:Nin,:)
6116            pin = percentages(s1,s2,s3,1:Nin)
6117
6118            ! Getting the values
6119            DO iv=1, Nin
6120              i1 = gin(iv,1)
6121              i2 = gin(iv,2)
6122              vin(iv,:) = varin(i1,i2,:)
6123            END DO
6124            DO i3=1, di3
6125              minv = fillVal64
6126              maxv = -fillVal64
6127              meanv = zeroRK
6128              mean2v = zeroRK
6129              stdv = zeroRK
6130              minv = MINVAL(vin(:,i3))
6131              maxv = MAXVAL(vin(:,i3))
6132              meanv = SUM(vin(:,i3)*pin)
6133              mean2v = SUM(vin(:,i3)**2*pin)
6134              DO iv=1,Nin
6135                stdv = stdv + ( (meanv - vin(iv,i3))*pin(iv) )**2
6136              END DO
6137              stdv = SQRT(stdv)
6138              svin = vin(:,i3)
6139              CALL SortR_K(svin, Nin)
6140              medv = svin(INT(Nin/2))
6141              varout(s1,s2,s3,i3,1) = minv
6142              varout(s1,s2,s3,i3,2) = maxv
6143              varout(s1,s2,s3,i3,3) = meanv
6144              varout(s1,s2,s3,i3,4) = mean2v
6145              varout(s1,s2,s3,i3,5) = stdv
6146              varout(s1,s2,s3,i3,6) = medv
6147              varout(s1,s2,s3,i3,7) = Nin*1.
6148            END DO
6149          ELSE
6150            i1 = gridsin(s1,s2,s3,1,1)
6151            i2 = gridsin(s1,s2,s3,1,2)
6152            varout(s1,s2,s3,:,1) = varin(i1,i2,:)
6153            varout(s1,s2,s3,:,2) = varin(i1,i2,:)
6154            varout(s1,s2,s3,:,3) = varin(i1,i2,:)
6155            varout(s1,s2,s3,:,4) = varin(i1,i2,:)*varin(i1,i2,:)
6156            varout(s1,s2,s3,:,5) = zeroRK
6157            varout(s1,s2,s3,:,6) = varin(i1,i2,:)
6158            varout(s1,s2,s3,:,7) = Nin*1.
6159          END IF
6160        END DO
6161      END DO
6162    END DO
6163
6164    IF (ALLOCATED(gin)) DEALLOCATE(gin)
6165    IF (ALLOCATED(pin)) DEALLOCATE(pin)
6166    IF (ALLOCATED(vin)) DEALLOCATE(vin)
6167    IF (ALLOCATED(svin)) DEALLOCATE(svin)
6168   
6169    RETURN
6170
6171  END SUBROUTINE multi_spaceweightstats_in3DRK3_slc3v3
6172
6173  SUBROUTINE multi_spaceweightstats_in3DRK3_slc3v4(varin, Ngridsin, gridsin, percentages, varout,     &
6174    di1, di2, di3, ds1, ds2, ds3, ds4, maxNgridsin)
6175  ! Subroutine to compute an spatial statistics value from a 3D RK matrix using 3rd dimension as
6176  !   running one into a matrix of 3-variables slices of rank 4 using spatial weights
6177
6178    IMPLICIT NONE
6179
6180    INTEGER, INTENT(in)                                  :: di1, di2, di3, ds1, ds2, ds3, ds4
6181    INTEGER, INTENT(in)                                  :: maxNgridsin
6182    INTEGER, DIMENSION(ds1,ds2,ds3,ds4), INTENT(in)      :: Ngridsin
6183    INTEGER, INTENT(in),                                                                              &
6184      DIMENSION(ds1,ds2,ds3,ds4,maxNgridsin,2)           :: gridsin
6185    REAL(r_k), DIMENSION(di1,di2,di3), INTENT(in)        :: varin
6186    REAL(r_k), INTENT(in),                                                                            &
6187      DIMENSION(ds1,ds2,ds3,ds4,maxNgridsin)             :: percentages
6188    REAL(r_k), DIMENSION(ds1,ds2,ds3,ds4,di3,7),                                                      &
6189      INTENT(out)                                        :: varout
6190
6191! Local
6192    INTEGER                                              :: i1, i2, i3, s1, s2, s3, s4, iv
6193    INTEGER                                              :: Ncounts, Nin
6194    CHARACTER(len=3)                                     :: val1S, val2S
6195    CHARACTER(len=30)                                    :: val3S
6196    REAL(r_k)                                            :: minv, maxv, meanv, mean2v, stdv, medv
6197    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: pin
6198    INTEGER, DIMENSION(:,:), ALLOCATABLE                 :: gin
6199    REAL(r_k), DIMENSION(:), ALLOCATABLE                 :: svin
6200    REAL(r_k), DIMENSION(:,:), ALLOCATABLE               :: vin
6201
6202!!!!!!! Variables
6203! di1, di2, di3: length of dimensions of the 3D matrix of values
6204! ds[1-4]: length of dimensions of matrix with the slices
6205! maxNgridsin: maximum number of grid points from the 3D matrix in any slice
6206! varin: 3D RK variable to be used
6207! Ngridsin: number of grids from 3D RK matrix for each slice
6208! gridsin: coordinates of grids of the 3D RK matrix B to matrix of slices
6209! percentages: weights as percentages of space of 3D RK matrix for each slice
6210!!!!!
6211! Available spatial statistics to compute inside each slice using values from 3D RK matrix
6212!   'min': minimum value
6213!   'max': maximum value
6214!   'mean': space weighted mean value
6215!   'mean2': space weighted quadratic mean value
6216!   'stddev': space weighted standard deviation value
6217!   'median': median value
6218!   'count': percentage of the space of matrix A covered by each different value of matrix B
6219! varout: output statistical variable
6220
6221    fname = 'multi_spaceweightstats_in3DRK3_slc3v4'
6222
6223    varout = fillval64
6224
6225    ! Let's be efficient?
6226    varout = fillVal64
6227    DO s1 =1, ds1
6228      DO s2 =1, ds2
6229        DO s3 =1, ds3
6230          DO s4 =1, ds4
6231            Nin = Ngridsin(s1,s2,s3,s4)
6232            IF (Nin > 1) THEN
6233              IF (ALLOCATED(gin)) DEALLOCATE(gin)
6234              ALLOCATE(gin(Nin,2))
6235              IF (ALLOCATED(pin)) DEALLOCATE(pin)
6236              ALLOCATE(pin(Nin))
6237              IF (ALLOCATED(vin)) DEALLOCATE(vin)
6238              ALLOCATE(vin(Nin,di3))
6239              IF (ALLOCATED(svin)) DEALLOCATE(svin)
6240              ALLOCATE(svin(Nin))
6241              gin = gridsin(s1,s2,s3,s4,1:Nin,:)
6242              pin = percentages(s1,s2,s3,s4,1:Nin)
6243
6244              ! Getting the values
6245              DO iv=1, Nin
6246                i1 = gin(iv,1)
6247                i2 = gin(iv,2)
6248                vin(iv,:) = varin(i1,i2,:)
6249              END DO
6250              ! Computing along d3
6251              DO i3=1, di3
6252                minv = fillVal64
6253                maxv = -fillVal64
6254                meanv = zeroRK
6255                mean2v = zeroRK
6256                stdv = zeroRK
6257
6258                minv = MINVAL(vin(:,i3))
6259                maxv = MAXVAL(vin(:,i3))
6260                meanv = SUM(vin(:,i3)*pin)
6261                mean2v = SUM(vin(:,i3)**2*pin) 
6262                DO iv=1,Nin
6263                  stdv = stdv + ( (meanv - vin(iv,i3))*pin(iv) )**2
6264                END DO
6265                stdv = SQRT(stdv)
6266                svin = vin(:,i3)
6267                CALL SortR_K(svin, Nin)
6268                medv = svin(INT(Nin/2))
6269                varout(s1,s2,s3,s4,i3,1) = minv
6270                varout(s1,s2,s3,s4,i3,2) = maxv
6271                varout(s1,s2,s3,s4,i3,3) = meanv
6272                varout(s1,s2,s3,s4,i3,4) = mean2v
6273                varout(s1,s2,s3,s4,i3,5) = stdv
6274                varout(s1,s2,s3,s4,i3,6) = medv
6275                varout(s1,s2,s3,s4,i3,7) = Nin*1.
6276              END DO
6277            ELSE
6278                i1 = gridsin(s1,s2,s3,s4,1,1)
6279                i2 = gridsin(s1,s2,s3,s4,1,2)
6280                varout(s1,s2,s3,s4,:,1) = varin(i1,i2,:)
6281                varout(s1,s2,s3,s4,:,2) = varin(i1,i2,:)
6282                varout(s1,s2,s3,s4,:,3) = varin(i1,i2,:)
6283                varout(s1,s2,s3,s4,:,4) = varin(i1,i2,:)*varin(i1,i2,:)
6284                varout(s1,s2,s3,s4,:,5) = zeroRK
6285                varout(s1,s2,s3,s4,:,6) = varin(i1,i2,:)
6286                varout(s1,s2,s3,s4,:,7) = Nin*1.
6287            END IF
6288          END DO
6289        END DO
6290      END DO
6291    END DO
6292
6293    IF (ALLOCATED(gin)) DEALLOCATE(gin)
6294    IF (ALLOCATED(pin)) DEALLOCATE(pin)
6295    IF (ALLOCATED(vin)) DEALLOCATE(vin)
6296    IF (ALLOCATED(svin)) DEALLOCATE(svin)
6297   
6298    RETURN
6299
6300  END SUBROUTINE multi_spaceweightstats_in3DRK3_slc3v4
6301
6302  SUBROUTINE multi_index_mat2DI(d1, d2, d12, mat, value, Nindices, indices)
6303  ! Subroutine to provide the indices of the different locations of a value inside a 2D integer matrix
6304
6305    IMPLICIT NONE
6306
6307    INTEGER, INTENT(in)                                  :: d1, d2, d12
6308    INTEGER, DIMENSION(d1,d2), INTENT(in)                :: mat
6309    INTEGER,INTENT(in)                                   :: value
6310    INTEGER, INTENT(out)                                 :: Nindices
6311    INTEGER, DIMENSION(2,d12), INTENT(out)               :: indices
6312
6313! Local
6314    INTEGER                                              :: i,j
6315    INTEGER                                              :: Ncounts1D, icount1D
6316    INTEGER, DIMENSION(d2)                               :: diffmat1D
6317
6318    !!!!!!! Variables
6319    ! d1, d2: shape of the 2D matrix
6320    ! mat: 2D matrix
6321    ! value: value to be looking for
6322    ! Nindices: number of times value found within matrix
6323    ! indices: indices of the found values
6324
6325    fname = 'multi_index_mat2DI'
6326
6327    Nindices = 0
6328    indices = 0
6329    DO i=1, d1
6330      diffmat1D = mat(i,:) - value
6331      IF (ANY(diffmat1D == 0)) THEN
6332        Ncounts1D = COUNT(diffmat1D == 0)
6333        icount1D = 0
6334        DO j=1, d2
6335          IF (diffmat1D(j) == 0) THEN
6336            Nindices = Nindices + 1
6337            indices(1,Nindices) = i
6338            indices(2,Nindices) = j
6339            icount1D = icount1D + 1
6340            IF (icount1D == Ncounts1D) EXIT
6341          END IF
6342        END DO
6343      END IF
6344    END DO
6345
6346  END SUBROUTINE multi_index_mat2DI
6347
6348  SUBROUTINE multi_index_mat3DI(d1, d2, d3, d123, mat, value, Nindices, indices)
6349  ! Subroutine to provide the indices of the different locations of a value inside a 3D integer matrix
6350
6351    IMPLICIT NONE
6352
6353    INTEGER, INTENT(in)                                  :: d1, d2, d3, d123
6354    INTEGER, DIMENSION(d1,d2,d3), INTENT(in)             :: mat
6355    INTEGER, INTENT(in)                                  :: value
6356    INTEGER, INTENT(out)                                 :: Nindices
6357    INTEGER, DIMENSION(3,d123), INTENT(out)              :: indices
6358
6359! Local
6360    INTEGER                                              :: i,j,k
6361    INTEGER                                              :: Ncounts1D, icount1D
6362    INTEGER                                              :: Ncounts2D, icount2D
6363    INTEGER, DIMENSION(d2,d3)                            :: diffmat2D
6364    INTEGER, DIMENSION(d3)                               :: diffmat1D
6365
6366    !!!!!!! Variables
6367    ! d1, d2, d3: shape of the 3D matrix
6368    ! mat: 3D matrix
6369    ! value: value to be looking for
6370    ! Nindices: number of times value found within matrix
6371    ! indices: indices of the found values
6372
6373    fname = 'multi_index_mat3DI'
6374
6375    Nindices = 0
6376    indices = 0
6377    DO i=1, d1
6378      diffmat2D = mat(i,:,:) - value
6379      IF (ANY(diffmat2D == 0)) THEN
6380        Ncounts2D = COUNT(diffmat2D == 0)
6381        icount2D = 0
6382        DO j=1, d2
6383          diffmat1D = mat(i,j,:) - value
6384          IF (ANY(diffmat1D == 0)) THEN
6385            Ncounts1D = COUNT(diffmat1D == 0)
6386            icount1D = 0
6387            DO k=1, d3
6388              IF (diffmat1D(k) == 0) THEN
6389                Nindices = Nindices + 1
6390                indices(1,Nindices) = i
6391                indices(2,Nindices) = j
6392                indices(3,Nindices) = k
6393                icount1D = icount1D + 1
6394                IF (icount1D == Ncounts1D) EXIT
6395              END IF
6396            END DO
6397            icount2D = icount2D + icount1D
6398            IF (icount2D == Ncounts2D) EXIT
6399          END IF
6400        END DO
6401      END IF
6402    END DO
6403
6404  END SUBROUTINE multi_index_mat3DI
6405
6406  SUBROUTINE multi_index_mat4DI(d1, d2, d3, d4, d1234, mat, value, Nindices, indices)
6407  ! Subroutine to provide the indices of the different locations of a value inside a 4D integer matrix
6408
6409    IMPLICIT NONE
6410
6411    INTEGER, INTENT(in)                                  :: d1, d2, d3, d4, d1234
6412    INTEGER, DIMENSION(d1,d2,d3,d4), INTENT(in)          :: mat
6413    INTEGER, INTENT(in)                                  :: value
6414    INTEGER, INTENT(out)                                 :: Nindices
6415    INTEGER, DIMENSION(4,d1234), INTENT(out)             :: indices
6416
6417! Local
6418    INTEGER                                              :: i,j,k,l
6419    INTEGER                                              :: Ncounts1D, icount1D
6420    INTEGER                                              :: Ncounts2D, icount2D
6421    INTEGER                                              :: Ncounts3D, icount3D
6422    INTEGER, DIMENSION(d2,d3,d4)                         :: diffmat3D
6423    INTEGER, DIMENSION(d3,d4)                            :: diffmat2D
6424    INTEGER, DIMENSION(d4)                               :: diffmat1D
6425
6426    !!!!!!! Variables
6427    ! d1, d2, d3, d4: shape of the 4D matrix
6428    ! mat: 4D matrix
6429    ! value: value to be looking for
6430    ! Nindices: number of times value found within matrix
6431    ! indices: indices of the found values
6432
6433    fname = 'multi_index_mat4DI'
6434
6435    Nindices = 0
6436    indices = 0
6437    DO i=1, d1
6438      diffmat3D = mat(i,:,:,:) - value
6439      IF (ANY(diffmat3D == 0)) THEN
6440        Ncounts3D = COUNT(diffmat3D == 0)
6441        icount3D = 0
6442        DO j=1, d2
6443          diffmat2D = mat(i,j,:,:) - value
6444          IF (ANY(diffmat2D == 0)) THEN
6445            Ncounts2D = COUNT(diffmat2D == 0)
6446            icount2D = 0
6447            DO k=1, d3
6448              diffmat1D = mat(i,j,k,:) - value
6449              IF (ANY(diffmat1D == 0)) THEN
6450                Ncounts1D = COUNT(diffmat1D == 0)
6451                icount1D = 0
6452                DO l=1, d4
6453                  IF (diffmat1D(l) == 0) THEN
6454                    Nindices = Nindices + 1
6455                    indices(1,Nindices) = i
6456                    indices(2,Nindices) = j
6457                    indices(3,Nindices) = k
6458                    indices(4,Nindices) = l
6459                    icount1D = icount1D + 1
6460                    IF (icount1D == Ncounts1D) EXIT
6461                  END IF
6462                END DO
6463              icount2D = icount2D + icount1D
6464              IF (icount2D == Ncounts2D) EXIT
6465              END IF
6466            END DO
6467            icount3D = icount3D + icount1D
6468            IF (icount3D == Ncounts3D) EXIT
6469          END IF
6470        END DO
6471      END IF
6472    END DO
6473
6474  END SUBROUTINE multi_index_mat4DI
6475
6476  SUBROUTINE multi_index_mat2DRK(d1, d2, d12, mat, value, Nindices, indices)
6477  ! Subroutine to provide the indices of the different locations of a value inside a 2D RK matrix
6478
6479    IMPLICIT NONE
6480
6481    INTEGER, INTENT(in)                                  :: d1, d2, d12
6482    REAL(r_k), DIMENSION(d1,d2), INTENT(in)              :: mat
6483    REAL(r_k),INTENT(in)                                 :: value
6484    INTEGER, INTENT(out)                                 :: Nindices
6485    INTEGER, DIMENSION(2,d12), INTENT(out)               :: indices
6486
6487! Local
6488    INTEGER                                              :: i,j
6489    INTEGER                                              :: Ncounts1D, icount1D
6490    REAL(r_k), DIMENSION(d2)                             :: diffmat1D
6491
6492    !!!!!!! Variables
6493    ! d1, d2: shape of the 2D matrix
6494    ! mat: 2D matrix
6495    ! value: value to be looking for
6496    ! Nindices: number of times value found within matrix
6497    ! indices: indices of the found values
6498
6499    fname = 'multi_index_mat2DRK'
6500
6501    Nindices = 0
6502    indices = 0
6503    DO i=1, d1
6504      diffmat1D = mat(i,:) - value
6505      IF (ANY(diffmat1D == zeroRK)) THEN
6506        Ncounts1D = COUNT(diffmat1D == zeroRK)
6507        icount1D = 0
6508        DO j=1, d2
6509          IF (diffmat1D(j) == zeroRK) THEN
6510            Nindices = Nindices + 1
6511            indices(1,Nindices) = i
6512            indices(2,Nindices) = j
6513            icount1D = icount1D + 1
6514            IF (icount1D == Ncounts1D) EXIT
6515          END IF
6516        END DO
6517      END IF
6518    END DO
6519
6520  END SUBROUTINE multi_index_mat2DRK
6521
6522  SUBROUTINE multi_index_mat3DRK(d1, d2, d3, d123, mat, value, Nindices, indices)
6523  ! Subroutine to provide the indices of the different locations of a value inside a 3D RK matrix
6524
6525    IMPLICIT NONE
6526
6527    INTEGER, INTENT(in)                                  :: d1, d2, d3, d123
6528    REAL(r_k), DIMENSION(d1,d2,d3), INTENT(in)           :: mat
6529    REAL(r_k),INTENT(in)                                 :: value
6530    INTEGER, INTENT(out)                                 :: Nindices
6531    INTEGER, DIMENSION(3,d123), INTENT(out)              :: indices
6532
6533! Local
6534    INTEGER                                              :: i,j,k
6535    INTEGER                                              :: Ncounts1D, icount1D
6536    INTEGER                                              :: Ncounts2D, icount2D
6537    REAL(r_k), DIMENSION(d2,d3)                          :: diffmat2D
6538    REAL(r_k), DIMENSION(d3)                             :: diffmat1D
6539
6540    !!!!!!! Variables
6541    ! d1, d2, d3: shape of the 3D matrix
6542    ! mat: 3D matrix
6543    ! value: value to be looking for
6544    ! Nindices: number of times value found within matrix
6545    ! indices: indices of the found values
6546
6547    fname = 'multi_index_mat3DRK'
6548
6549    Nindices = 0
6550    indices = 0
6551    DO i=1, d1
6552      diffmat2D = mat(i,:,:) - value
6553      IF (ANY(diffmat2D == zeroRK)) THEN
6554        Ncounts2D = COUNT(diffmat2D == zeroRK)
6555        icount2D = 0
6556        DO j=1, d2
6557          diffmat1D = mat(i,j,:) - value
6558          IF (ANY(diffmat1D == zeroRK)) THEN
6559            Ncounts1D = COUNT(diffmat1D == zeroRK)
6560            icount1D = 0
6561            DO k=1, d3
6562              IF (diffmat1D(k) == zeroRK) THEN
6563                Nindices = Nindices + 1
6564                indices(1,Nindices) = i
6565                indices(2,Nindices) = j
6566                indices(3,Nindices) = k
6567                icount1D = icount1D + 1
6568                IF (icount1D == Ncounts1D) EXIT
6569              END IF
6570            END DO
6571            icount2D = icount2D + icount1D
6572            IF (icount2D == Ncounts2D) EXIT
6573          END IF
6574        END DO
6575      END IF
6576    END DO
6577
6578  END SUBROUTINE multi_index_mat3DRK
6579
6580  SUBROUTINE multi_index_mat4DRK(d1, d2, d3, d4, d1234, mat, value, Nindices, indices)
6581  ! Subroutine to provide the indices of the different locations of a value inside a 4D RK matrix
6582
6583    IMPLICIT NONE
6584
6585    INTEGER, INTENT(in)                                  :: d1, d2, d3, d4, d1234
6586    REAL(r_k), DIMENSION(d1,d2,d3,d4), INTENT(in)        :: mat
6587    REAL(r_k),INTENT(in)                                 :: value
6588    INTEGER, INTENT(out)                                 :: Nindices
6589    INTEGER, DIMENSION(4,d1234), INTENT(out)             :: indices
6590
6591! Local
6592    INTEGER                                              :: i,j,k,l
6593    INTEGER                                              :: Ncounts1D, icount1D
6594    INTEGER                                              :: Ncounts2D, icount2D
6595    INTEGER                                              :: Ncounts3D, icount3D
6596    REAL(r_k), DIMENSION(d2,d3,d4)                       :: diffmat3D
6597    REAL(r_k), DIMENSION(d3,d4)                          :: diffmat2D
6598    REAL(r_k), DIMENSION(d4)                             :: diffmat1D
6599
6600    !!!!!!! Variables
6601    ! d1, d2, d3, d4: shape of the 4D matrix
6602    ! mat: 4D matrix
6603    ! value: value to be looking for
6604    ! Nindices: number of times value found within matrix
6605    ! indices: indices of the found values
6606
6607    fname = 'multi_index_mat4DRK'
6608
6609    Nindices = 0
6610    indices = 0
6611    DO i=1, d1
6612      diffmat3D = mat(i,:,:,:) - value
6613      IF (ANY(diffmat3D == zeroRK)) THEN
6614        Ncounts3D = COUNT(diffmat3D == zeroRK)
6615        icount3D = 0
6616        DO j=1, d2
6617          diffmat2D = mat(i,j,:,:) - value
6618          IF (ANY(diffmat2D == zeroRK)) THEN
6619            Ncounts2D = COUNT(diffmat2D == zeroRK)
6620            icount2D = 0
6621            DO k=1, d3
6622              diffmat1D = mat(i,j,k,:) - value
6623              IF (ANY(diffmat1D == zeroRK)) THEN
6624                Ncounts1D = COUNT(diffmat1D == zeroRK)
6625                icount1D = 0
6626                DO l=1, d4
6627                  IF (diffmat1D(l) == zeroRK) THEN
6628                    Nindices = Nindices + 1
6629                    indices(1,Nindices) = i
6630                    indices(2,Nindices) = j
6631                    indices(3,Nindices) = k
6632                    indices(4,Nindices) = l
6633                    icount1D = icount1D + 1
6634                    IF (icount1D == Ncounts1D) EXIT
6635                  END IF
6636                END DO
6637              icount2D = icount2D + icount1D
6638              IF (icount2D == Ncounts2D) EXIT
6639              END IF
6640            END DO
6641            icount3D = icount3D + icount1D
6642            IF (icount3D == Ncounts3D) EXIT
6643          END IF
6644        END DO
6645      END IF
6646    END DO
6647
6648  END SUBROUTINE multi_index_mat4DRK
6649
6650  SUBROUTINE coincident_list_2Dcoords(NpointsA, pointsA, NpointsB, pointsB, Npoints, points, inpA,    &
6651    inpB)
6652  ! Subroutine to determine which 2D points of an A list are also found in a B list
6653
6654    IMPLICIT NONE
6655
6656    INTEGER, INTENT(in)                                  :: NpointsA, NpointsB
6657    INTEGER, DIMENSION(NpointsA,2), INTENT(in)           :: pointsA
6658    INTEGER, DIMENSION(NpointsB,2), INTENT(in)           :: pointsB
6659    INTEGER, INTENT(out)                                 :: Npoints
6660    INTEGER, DIMENSION(NpointsA,2), INTENT(out)          :: points
6661    INTEGER, DIMENSION(NpointsA), INTENT(out)            :: inpA, inpB
6662
6663    ! Local
6664    INTEGER                                              :: iA, iB
6665
6666!!!!!!! Variables
6667! NpointsA: Number of points of the list A
6668! pointsA: points of the list A
6669! NpointsB: Number of points of the list B
6670! pointsB: points of the list B
6671! Npoints: Number of coincident points
6672! points: coincident points
6673! inpA: coincident points list A
6674! inpB: coincident points list B
6675
6676
6677    fname = 'coincident_list_2Dcoords'
6678
6679    Npoints = 0
6680    points = 0
6681    inpA = 0
6682    inpB = 0
6683
6684    DO iA = 1, NpointsA
6685      DO iB = 1, NpointsB
6686        IF ( (pointsA(iA,1) == pointsB(iB,1)) .AND. (pointsA(iA,2) == pointsB(iB,2)) ) THEN
6687          Npoints = Npoints + 1
6688          points(Npoints,1) = pointsA(iA,1)
6689          points(Npoints,2) = pointsA(iA,2)
6690          inpA(Npoints) = iA
6691          inpB(Npoints) = iB
6692          EXIT
6693        END IF
6694
6695      END DO
6696    END DO
6697
6698  END SUBROUTINE coincident_list_2Dcoords
6699
6700  SUBROUTINE coincident_gridsin2D_old(dxA, dyA, dxyA, NpointsA, pointsA, dxB, dyB, dxyB, NpointsB,    &
6701    pointsB, Npoints, points, inpointsA, inpointsB)
6702  ! Subroutine to determine which lists of 2D gridsin points of an A list are also found in a B list
6703
6704    IMPLICIT NONE
6705
6706    INTEGER, INTENT(in)                                  :: dxA, dyA, dxyA
6707    INTEGER, INTENT(in)                                  :: dxB, dyB, dxyB
6708    INTEGER, DIMENSION(dxA, dyA), INTENT(in)             :: NpointsA
6709    INTEGER, DIMENSION(dxB, dyB), INTENT(in)             :: NpointsB
6710    INTEGER, DIMENSION(dxA, dyA, dxyA, 2), INTENT(in)    :: pointsA
6711    INTEGER, DIMENSION(dxB, dyB, dxyB, 2), INTENT(in)    :: pointsB
6712    INTEGER, DIMENSION(dxA, dyA, dxB, dyB), INTENT(out)  :: Npoints
6713    INTEGER, DIMENSION(dxA, dyA, dxB, dyB, dxyA, 2),                                                  &
6714      INTENT(out)                                        :: points
6715    INTEGER, DIMENSION(dxA, dyA, dxB, dyB, dxyA),                                                     &
6716      INTENT(out)                                        :: inpointsA
6717    INTEGER, DIMENSION(dxA, dyA, dxB, dyB, dxyA),                                                     &
6718      INTENT(out)                                        :: inpointsB
6719
6720    ! Local
6721    INTEGER                                              :: ixA, iyA, ixB, iyB, iv, ii
6722    INTEGER                                              :: NA, NB
6723    INTEGER, DIMENSION(dxyA)                             :: ptsA, ptsB
6724    INTEGER, DIMENSION(dxyA, 2)                          :: pts
6725
6726
6727!!!!!!! Variables
6728! dxA, dyA: 2D shape of the list A
6729! NpointsA: 2D Number of points of the list A
6730! pointsA: points of the list A
6731! dxB, dyB: 2D shape of the list B
6732! NpointsB: 2D Number of points of the list B
6733! pointsB: points of the list B
6734! Npoints: Number of coincident points
6735! points: coincident points
6736! inpointsA: coincident points list A
6737! inpointsB: coincident points list B
6738
6739    fname = 'coincident_gridsin2D_old'
6740
6741    Npoints = 0
6742    points = 0
6743    inpointsA = 0
6744    inpointsB = 0
6745
6746    DO ixA=1, dxA
6747      DO iyA=1, dyA
6748        NA = NpointsA(ixA,iyA)
6749        DO ixB=1, dxB
6750          DO iyB=1, dyB
6751            NB = NpointsB(ixB,iyB)
6752            pts = -1
6753            CALL coincident_list_2Dcoords(NA, pointsA(ixA,iyA,1:NA,:), NB, pointsB(ixB,iyB,1:NB,:),   &
6754              Npoints(ixA,iyA,ixB,iyB), pts(1:NA,:), ptsA, ptsB)
6755            DO iv = 1, Npoints(ixA,iyA,ixB,iyB)
6756              points(ixA,iyA,ixB,iyB,iv,1) = pts(iv,1)
6757              points(ixA,iyA,ixB,iyB,iv,2) = pts(iv,2)
6758              inpointsA(ixA,iyA,ixB,iyB,iv) = ptsA(iv)
6759              inpointsB(ixA,iyA,ixB,iyB,iv) = ptsB(iv)
6760            END DO
6761          END DO
6762        END DO
6763      END DO
6764    END DO
6765
6766  END SUBROUTINE coincident_gridsin2D_old
6767
6768  SUBROUTINE coincident_gridsin2D(dxA, dyA, dxyA, NpointsA, pointsA, dxB, dyB, dxyB, NpointsB,        &
6769    pointsB, Npoints, points, inpointsA, inpointsB)
6770  ! Subroutine to determine which lists of 2D gridsin points of an A list are also found in a B list
6771
6772    IMPLICIT NONE
6773
6774    INTEGER, INTENT(in)                                  :: dxA, dyA, dxyA
6775    INTEGER, INTENT(in)                                  :: dxB, dyB, dxyB
6776    INTEGER, DIMENSION(dxA, dyA), INTENT(in)             :: NpointsA
6777    INTEGER, DIMENSION(dxB, dyB), INTENT(in)             :: NpointsB
6778    INTEGER, DIMENSION(dxA, dyA, dxyA, 2), INTENT(in)    :: pointsA
6779    INTEGER, DIMENSION(dxB, dyB, dxyB, 2), INTENT(in)    :: pointsB
6780    INTEGER, DIMENSION(dxA, dyA, dxB, dyB), INTENT(out)  :: Npoints
6781    INTEGER, DIMENSION(dxA, dyA, dxB, dyB, dxyA, 2),                                                  &
6782      INTENT(out)                                        :: points
6783    INTEGER, DIMENSION(dxA, dyA, dxB, dyB, dxyA),                                                     &
6784      INTENT(out)                                        :: inpointsA
6785    INTEGER, DIMENSION(dxA, dyA, dxB, dyB, dxyA),                                                     &
6786      INTENT(out)                                        :: inpointsB
6787
6788    ! Local
6789    INTEGER                                              :: ixA, iyA, ixB, iyB, iv, iv1, iv2
6790    INTEGER                                              :: NA, NB
6791    INTEGER, DIMENSION(dxyA)                             :: ptsA, ptsB
6792    INTEGER, DIMENSION(dxyA, 2)                          :: pts
6793
6794
6795!!!!!!! Variables
6796! dxA, dyA: 2D shape of the list A
6797! NpointsA: 2D Number of points of the list A
6798! pointsA: points of the list A
6799! dxB, dyB: 2D shape of the list B
6800! NpointsB: 2D Number of points of the list B
6801! pointsB: points of the list B
6802! Npoints: Number of coincident points
6803! points: coincident points
6804! inpointsA: coincident points list A
6805! inpointsB: coincident points list B
6806
6807    fname = 'coincident_gridsin2D'
6808
6809    Npoints = 0
6810    points = 0
6811    inpointsA = 0
6812    inpointsB = 0
6813
6814    DO ixA=1, dxA
6815      DO iyA=1, dyA
6816        NA = NpointsA(ixA,iyA)
6817        DO ixB=1, dxB
6818          DO iyB=1, dyB
6819            NB = NpointsB(ixB,iyB)
6820            iv = 0
6821            DO iv1=1, NA
6822              DO iv2=1, NB
6823                IF ( (pointsA(ixA,iyA,iv1,1) == pointsB(ixB,iyB,iv2,1)) .AND.                         &
6824                  (pointsA(ixA,iyA,iv1,2) == pointsB(ixB,iyB,iv2,2)) ) THEN
6825                  iv = iv + 1
6826                  points(ixA,iyA,ixB,iyB,iv,1) = pointsA(ixA,iyA,iv1,1)
6827                  points(ixA,iyA,ixB,iyB,iv,2) = pointsA(ixA,iyA,iv1,2)
6828                  inpointsA(ixA,iyA,ixB,iyB,iv) = iv1
6829                  inpointsB(ixA,iyA,ixB,iyB,iv) = iv2
6830                END IF
6831              END DO
6832            END DO
6833            Npoints(ixA,iyA,ixB,iyB) = iv
6834          END DO
6835        END DO
6836      END DO
6837    END DO   
6838
6839  END SUBROUTINE coincident_gridsin2D
6840
6841END MODULE module_scientific
Note: See TracBrowser for help on using the repository browser.