source: palm/trunk/UTIL/read_prt_data.f90 @ 2124

Last change on this file since 2124 was 2124, checked in by hoffmann, 7 years ago

read_prt_data.f90 adapted to new variable names

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