source: palm/tags/release-5.0/UTIL/read_prt_data.f90 @ 4106

Last change on this file since 4106 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

File size: 6.9 KB
Line 
1 PROGRAM read_prt_data
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017  Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: read_prt_data.f90 2123 2017-01-18 12:49:59Z hoffmann $
27!
28! 2123 2017-01-18 12:49:59Z hoffmann
29! Particle variables renamed: tailpoints, tail_id, and dvrp_psize to id1, id2,
30! and user
31!
32! 1771 2016-02-29 10:57:56Z hoffmann
33! Initial revision.
34!
35! Description:
36! ------------
37! This routine reads the particle data generated by PALM, and enables user
38! analysis. Compile and execute this program in the folder where your particle
39! data (_000000, _000001, ...) is stored.
40!------------------------------------------------------------------------------!
41
42    IMPLICIT NONE
43
44    CHARACTER(LEN=7)    ::  i_proc_char
45    CHARACTER (LEN=80)  ::  rtext
46    CHARACTER (LEN=110) ::  run_description_header
47
48    REAL(KIND=8) ::  simulated_time
49    INTEGER      ::  ip, i_proc=0, i_proc_end, jp, kp,                         &
50                     max_number_of_particle_groups, number_of_particles,       &
51                     number_of_particle_groups, n, nxl,                        &
52                     nxr, nys, nyn, nzb, nzt, nbgp, status
53
54    INTEGER, DIMENSION(:,:,:), ALLOCATABLE ::  prt_count
55
56    TYPE particle_type
57       SEQUENCE
58       REAL(KIND=8) ::  radius, age, age_m, dt_sum, user, e_m,                 &
59                        origin_x, origin_y, origin_z, rvar1, rvar2, rvar3,     &
60                        speed_x, speed_y, speed_z, weight_factor, x, y, z
61      INTEGER       ::  class, group, id1, id2
62      LOGICAL       ::  particle_mask
63      INTEGER       ::  block_nr
64    END TYPE particle_type
65
66    TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  particles_temp
67    TYPE(particle_type), DIMENSION(:), POINTER     ::  particles
68
69    TYPE  grid_particle_def
70       TYPE(particle_type), DIMENSION(:), ALLOCATABLE ::  particles
71    END TYPE grid_particle_def
72
73    TYPE(grid_particle_def), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  grid_particles
74
75    TYPE particle_groups_type
76        SEQUENCE
77        REAL(KIND=8) ::  density_ratio, radius, exp_arg, exp_term
78    END TYPE particle_groups_type
79
80    TYPE(particle_groups_type), DIMENSION(:), ALLOCATABLE ::  particle_groups
81
82    LOGICAL ::  found
83!
84!-- Check if file from PE0 exists and terminate program if it doesn't.
85    WRITE (i_proc_char,'(''_'',I6.6)')  i_proc
86    INQUIRE ( FILE=i_proc_char, EXIST=found )
87!
88!-- Estimate the number of files (equal to the number of PEs which
89!-- have been used in PALM)
90    DO  WHILE ( found )
91       OPEN ( 85, FILE=i_proc_char, FORM='UNFORMATTED' )
92       i_proc = i_proc + 1
93       WRITE (i_proc_char,'(''_'',I6.6)')  i_proc
94       INQUIRE ( FILE=i_proc_char, EXIST=found )
95       CLOSE( 85 )
96    ENDDO
97!
98!-- Info-output
99    PRINT*, ''
100    PRINT*, '*** read_prt ***'
101    IF ( i_proc /= 0 )  THEN
102       PRINT*, '***', i_proc, ' file(s) found'
103    ELSE
104       PRINT*, '+++ file _000000 not found'
105       PRINT*, '    program terminated'
106       STOP
107    ENDIF
108!
109!-- Set number of files and opens them sequentially
110    i_proc_end = i_proc-1
111
112    DO  i_proc = 0, i_proc_end
113!
114!--    Open particle data file for each process
115       WRITE (i_proc_char,'(''_'',I6.6)')  i_proc
116       OPEN ( 85, FILE=i_proc_char, FORM='UNFORMATTED' ) 
117!
118!--    Read general description of file and inform user
119       READ ( 85 )  run_description_header
120       READ ( 85 )  rtext
121       IF ( i_proc == 0 )  THEN
122          PRINT*, ' '
123          PRINT*, '*** data description header:'
124          PRINT*, '*** ', run_description_header
125          PRINT*, '*** ', rtext
126          PRINT*, ' '
127       ENDIF
128       PRINT*, '*** data of file', i_proc, 'is analysed'
129       READ ( 85 )  number_of_particle_groups, max_number_of_particle_groups
130
131       IF ( .NOT. ALLOCATED(particle_groups) )  THEN
132          ALLOCATE( particle_groups(max_number_of_particle_groups) )
133       ENDIF
134   
135       READ ( 85 )  particle_groups
136       READ ( 85 )  nxl, nxr, nys, nyn, nzb, nzt, nbgp
137
138       IF ( ALLOCATED(prt_count)  .OR.  ALLOCATED(grid_particles) )  THEN
139          DEALLOCATE( prt_count, grid_particles )
140       ENDIF
141
142       ALLOCATE( prt_count(nzb:nzt+1,nys-nbgp:nyn+nbgp,nxl-nbgp:nxr+nbgp),     &
143                 grid_particles(nzb+1:nzt,nys:nyn,nxl:nxr) )
144
145!
146!--    Start individual time loop
147       DO
148          READ( 85, IOSTAT=status)  simulated_time
149          IF ( status < 0 )  THEN
150             PRINT*, '*** end of file reached'
151             EXIT
152          ENDIF
153          PRINT*, '*** time of analyzed data set:', simulated_time
154
155          READ ( 85 )  prt_count
156
157          DO  ip = nxl, nxr
158             DO  jp = nys, nyn
159                DO  kp = nzb+1, nzt
160                   number_of_particles = prt_count(kp,jp,ip)
161                   IF ( number_of_particles <= 0 )  CYCLE
162                   ALLOCATE( grid_particles(kp,jp,ip)%particles(1:number_of_particles) )
163                   ALLOCATE( particles_temp(1:number_of_particles) )
164                   READ ( 85 )  particles_temp
165                   grid_particles(kp,jp,ip)%particles = particles_temp
166                   DEALLOCATE( particles_temp )
167                ENDDO
168             ENDDO
169          ENDDO
170!
171!--       This part can be used for user analysis
172          DO  ip = nxl, nxr
173             DO  jp = nys, nyn
174                DO  kp = nzb+1, nzt
175                   number_of_particles = prt_count(kp,jp,ip)
176                   IF ( number_of_particles <= 0 )  CYCLE
177                   particles => grid_particles(kp,jp,ip)%particles
178!
179!--                Add your analysis here
180!                   DO  n = 1, number_of_particles
181!
182!                   ENDDO
183
184                ENDDO
185             ENDDO
186          ENDDO
187!
188!--       Deallocate grid_particles%particles in case of more than one timestep
189          DO  ip = nxl, nxr
190             DO  jp = nys, nyn
191                DO  kp = nzb+1, nzt
192                   number_of_particles = prt_count(kp,jp,ip)
193                   IF ( number_of_particles <= 0 )  CYCLE
194                   DEALLOCATE( grid_particles(kp,jp,ip)%particles )
195                ENDDO
196             ENDDO
197          ENDDO     
198
199       ENDDO ! end of time loop
200
201       CLOSE( 85 )
202
203    ENDDO ! end of file loop
204
205 END PROGRAM read_prt_data
Note: See TracBrowser for help on using the repository browser.