source: palm/tags/release-5.0/UTIL/compare_palm_logs.f90 @ 4383

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

Merge of branch palm4u into trunk

  • Property svn:keywords set to Id
File size: 11.1 KB
Line 
1 PROGRAM compare_palm_logs
2
3!------------------------------------------------------------------------------!
4! This file is part of the PALM model system.
5!
6! PALM is free software: you can redistribute it and/or modify it under the
7! terms of the GNU General Public License as published by the Free Software
8! Foundation, either version 3 of the License, or (at your option) any later
9! version.
10!
11! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
12! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
13! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
14!
15! You should have received a copy of the GNU General Public License along with
16! PALM. If not, see <http://www.gnu.org/licenses/>.
17!
18! Copyright 1997-2017  Leibniz Universitaet Hannover
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24! Former revisions:
25! -----------------
26! $Id: compare_palm_logs.f90 2696 2017-12-14 17:12:51Z Giersch $
27!
28! 1046 2012-11-09 14:38:45Z maronga
29! code put under GPL (PALM 3.9)
30! name of data-directories are read from input
31!
32! Description:
33! ------------
34! This routine compares the log files from two different PALM runs.
35!
36! This routine must be compiled with:
37! decalpha:
38!    f95 -cpp -fast -r8
39! IBM-Regatta:
40!    xlf95 -qsuffix=cpp=f90 -qrealsize=8 -q64 -qmaxmem=-1 -Q -O3
41! IMUK:
42!    ifort compare...f90 -o compare...x
43!    -cpp -axW -r8 -nbs -Vaxlib
44! NEC-SX6:
45!    sxf90 compare...f90 -o compare...x
46!    -C hopt -Wf '-A idbl4'
47!------------------------------------------------------------------------------!
48
49    IMPLICIT NONE
50
51!
52!-- Local variables
53    CHARACTER (LEN=5) ::  id_char
54    CHARACTER (LEN=80), DIMENSION(2)  ::  directory, log_message
55    CHARACTER (LEN=100), DIMENSION(2) ::  filename
56
57    INTEGER ::  count=0, i, id, i1(2), i2(2), j, j1(2), j2(2), k, k1(2), k2(2), &
58                n_err, n_files(2)
59
60    LOGICAL ::  found
61
62    REAL    ::  simtime(2)
63
64    INTEGER, DIMENSION(:,:),   ALLOCATABLE ::  array_2d_i_1, array_2d_i_2
65
66    REAL, DIMENSION(:,:),   ALLOCATABLE ::  array_2d_1, array_2d_2
67    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  array_1, array_2
68
69
70!
71!-- Read the two data-directories to be compared
72    PRINT*, '*** please enter name of first data-directory:'
73    READ ( *, * )  directory(1)
74    directory(1) = TRIM( directory(1) ) // '/'
75
76    PRINT*, '*** please enter name of second data-directory:'
77    READ ( *, * )  directory(2)
78    directory(2) = TRIM( directory(2) ) // '/'
79
80!
81!-- Check, if file from PE0 exists on directory 1. Stop, if it does not exist.
82    n_files(1) = 0
83
84    WRITE (id_char,'(''_'',I4.4)')  n_files(1)
85    INQUIRE ( FILE=TRIM( directory(1) )//id_char, EXIST=found )
86!
87!-- Find out the number of files (equal to the number of PEs which
88!-- have been used in PALM) and open them
89    DO  WHILE ( found )
90
91       OPEN ( n_files(1)+100, FILE=TRIM( directory(1) )//id_char, &
92              FORM='UNFORMATTED' )
93       n_files(1) = n_files(1) + 1
94       WRITE (id_char,'(''_'',I4.4)')  n_files(1)
95       INQUIRE ( FILE=TRIM( directory(1) )//id_char, EXIST=found )
96
97    ENDDO
98
99    IF ( n_files(1) == 0 )  THEN
100       PRINT*, '+++ no file _0000 in directory "', TRIM( directory(1) ), '"'
101       STOP
102    ELSE
103       PRINT*, '*** directory "', TRIM( directory(1) ), '": ', n_files(1), &
104               ' files found'
105    ENDIF
106
107!
108!-- Same for the second directory
109    n_files(2) = 0
110
111    WRITE (id_char,'(''_'',I4.4)')  n_files(2)
112    INQUIRE ( FILE=TRIM( directory(2) )//id_char, EXIST=found )
113
114    DO  WHILE ( found )
115
116       OPEN ( n_files(2)+200, FILE=TRIM( directory(2) )//id_char, &
117              FORM='UNFORMATTED' )
118       n_files(2) = n_files(2) + 1
119       WRITE (id_char,'(''_'',I4.4)')  n_files(2)
120       INQUIRE ( FILE=TRIM( directory(2) )//id_char, EXIST=found )
121
122    ENDDO
123
124!
125!-- Number of files must be identical
126    IF ( n_files(1) /= n_files(2) )  THEN
127       PRINT*, '+++ file number mismatch'
128       PRINT*, '    ', TRIM( directory(1) ), ': ', n_files(1), ' files'
129       PRINT*, '    ', TRIM( directory(2) ), ': ', n_files(2), ' files'
130       STOP
131    ENDIF
132
133!
134!-- Compare the data file by file
135    DO  id = 0, n_files(1)-1
136
137       count = 0
138
139       WRITE (filename(1),'(A,''_'',I4.4)')  TRIM( directory(1) ), id
140       WRITE (filename(2),'(A,''_'',I4.4)')  TRIM( directory(2) ), id
141
142       PRINT*, '*** comparing files "', TRIM( filename(1) ),'" "', &
143               TRIM( filename(2) ), '"'
144       DO
145          PRINT*,' '
146          READ ( id+100, END=100 )  log_message(1)
147          PRINT*,'    --- ', TRIM( log_message(1) )
148          READ ( id+200, END=900 )  log_message(2)
149
150          IF ( TRIM( log_message(1) ) /= TRIM( log_message(2) ) )  THEN
151             PRINT*,'    +++ log message on file 2 does not match:'
152             PRINT*,'        ', TRIM( log_message(2) )
153          ENDIF
154
155          count = count + 1
156          IF ( log_message(1)(1:2) == '3d' )  THEN
157             PRINT*,'    *** reading 3d array'
158             READ ( id+100, END=901 )  simtime(1), i1(1), i2(1), j1(1), j2(1), &
159                                       k1(1), k2(1)
160             PRINT*,'        time=', simtime(1)
161             PRINT*,'        array size=(',i1(1),':',i2(1), &
162                                       ',',j1(1),':',j2(1),',',k1(1),':',k2(1),')'
163             READ ( id+200, END=902 )  simtime(2), i1(2), i2(2), j1(2), j2(2), &
164                                       k1(2), k2(2)
165             IF ( simtime(1) /= simtime(2) .OR. i1(1) /= i1(2) .OR. &
166                  i2(1) /= i2(2) .OR. j1(1) /= j1(2) .OR. j2(1) /= j2(2) .OR. &
167                  k1(1) /= k1(2) .OR. k2(1) /= k2(2) )  THEN
168                PRINT*,'    +++ time/indices on file 2 does not match:'
169                PRINT*,'        time=', simtime(2)
170                PRINT*,'        array size=(',i1(2),':', &
171                                i2(2), ',',j1(2),':',j2(2),',',k1(2),':',k2(2),')'
172                STOP
173             ENDIF
174
175             ALLOCATE( array_1(i1(1):i2(1),j1(1):j2(1),k1(1):k2(1)), &
176                       array_2(i1(2):i2(2),j1(2):j2(2),k1(2):k2(2)) )
177
178             READ ( id+100, END=903 )  array_1
179             READ ( id+200, END=904 )  array_2
180
181             n_err = 0
182loop:        DO  k = k1(1), k2(1)
183loop1:           DO  j = j1(1), j2(1)
184                   DO  i = i1(1), i2(1)
185                      IF ( array_1(i,j,k) /= array_2(i,j,k) )  THEN
186                         PRINT*,'+++ data mismatch on element (',i,',',j,',',k,')'
187                         PRINT*,'    array_1: ', array_1(i,j,k)
188                         PRINT*,'    array_2: ', array_2(i,j,k)
189                         n_err = n_err + 1
190                         IF ( n_err > 5 )  EXIT loop
191                      ENDIF
192                   ENDDO
193                ENDDO loop1
194             ENDDO loop
195
196             DEALLOCATE( array_1, array_2 )
197
198          ELSEIF ( log_message(1)(1:2) == '2d' )  THEN
199             PRINT*,'    *** reading 2d array'
200             READ ( id+100, END=901 )  simtime(1), i1(1), i2(1), j1(1), j2(1)
201             PRINT*,'        time=', simtime(1)
202             PRINT*,'        array size=(',i1(1),':',i2(1), &
203                                       ',',j1(1),':',j2(1),')'
204             READ ( id+200, END=902 )  simtime(2), i1(2), i2(2), j1(2), j2(2)
205             IF ( simtime(1) /= simtime(2) .OR. i1(1) /= i1(2) .OR. &
206                  i2(1) /= i2(2) .OR. j1(1) /= j1(2) .OR. j2(1) /= j2(2) )  THEN
207                PRINT*,'    +++ time/indices on file 2 does not match:'
208                PRINT*,'        time=', simtime(2)
209                PRINT*,'        array size=(',i1(2),':', &
210                                i2(2), ',',j1(2),':',j2(2),')'
211             ENDIF
212
213             ALLOCATE( array_2d_1(i1(1):i2(1),j1(1):j2(1)), &
214                       array_2d_2(i1(2):i2(2),j1(2):j2(2)) )
215
216             READ ( id+100, END=903 )  array_2d_1
217             READ ( id+200, END=904 )  array_2d_2
218
219             IF ( i1(1) /= i1(2) )  i1(1) = i1(2)
220             IF ( i2(1) /= i2(2) )  i2(1) = i2(2)
221             IF ( j1(1) /= j1(2) )  j1(1) = j1(2)
222             IF ( j2(1) /= j2(2) )  j2(1) = j2(2)
223
224             n_err = 0
225loop2:       DO  j = j1(1), j2(1)
226                DO  i = i1(1), i2(1)
227                   IF ( array_2d_1(i,j) /= array_2d_2(i,j) )  THEN
228                      PRINT*,'+++ data mismatch on element (',i,',',j,')'
229                      PRINT*,'    array_1: ', array_2d_1(i,j)
230                      PRINT*,'    array_2: ', array_2d_2(i,j)
231                      n_err = n_err + 1
232                      IF ( n_err > 5 )  EXIT loop2
233                   ENDIF
234                ENDDO
235             ENDDO loop2
236
237             DEALLOCATE( array_2d_1, array_2d_2 )
238
239          ELSE
240             PRINT*,'    *** reading 2d int array'
241             READ ( id+100, END=901 )  simtime(1), i1(1), i2(1), j1(1), j2(1)
242             PRINT*,'        time=', simtime(1)
243             PRINT*,'        array size=(',i1(1),':',i2(1), &
244                                       ',',j1(1),':',j2(1),')'
245             READ ( id+200, END=902 )  simtime(2), i1(2), i2(2), j1(2), j2(2)
246             IF ( simtime(1) /= simtime(2) .OR. i1(1) /= i1(2) .OR. &
247                  i2(1) /= i2(2) .OR. j1(1) /= j1(2) .OR. j2(1) /= j2(2) )  THEN
248                PRINT*,'    +++ time/indices on file 2 does not match:'
249                PRINT*,'        time=', simtime(2)
250                PRINT*,'        array size=(',i1(2),':', &
251                                i2(2), ',',j1(2),':',j2(2),')'
252             ENDIF
253
254             ALLOCATE( array_2d_i_1(i1(1):i2(1),j1(1):j2(1)), &
255                       array_2d_i_2(i1(2):i2(2),j1(2):j2(2)) )
256
257             READ ( id+100, END=903 )  array_2d_i_1
258             READ ( id+200, END=904 )  array_2d_i_2
259
260             IF ( i1(1) /= i1(2) )  i1(1) = i1(2)
261             IF ( i2(1) /= i2(2) )  i2(1) = i2(2)
262             IF ( j1(1) /= j1(2) )  j1(1) = j1(2)
263             IF ( j2(1) /= j2(2) )  j2(1) = j2(2)
264
265             n_err = 0
266loop3:       DO  j = j1(1), j2(1)
267                DO  i = i1(1), i2(1)
268                   IF ( array_2d_i_1(i,j) /= array_2d_i_2(i,j) )  THEN
269                      PRINT*,'+++ data mismatch on element (',i,',',j,')'
270                      PRINT*,'    array_1: ', array_2d_i_1(i,j)
271                      PRINT*,'    array_2: ', array_2d_i_2(i,j)
272                      n_err = n_err + 1
273                      IF ( n_err > 5 )  EXIT loop3
274                   ENDIF
275                ENDDO
276             ENDDO loop3
277
278             DEALLOCATE( array_2d_i_1, array_2d_i_2 )
279
280          ENDIF
281
282!          IF ( count > 8 )  STOP
283       ENDDO
284
285100    PRINT*, '*** end of data on file "', TRIM( filename(1) ), '"'
286       PRINT*, '*** files seem to be identical'
287       PRINT*, ' '
288    ENDDO
289
290    STOP
291
292900 PRINT*,'+++ unexpected end on file "', TRIM( filename(2) ), '"'
293    STOP
294901 PRINT*,'+++ unexpected end on file "', TRIM( filename(1) ), '"'
295    PRINT*,'    while reading indices'
296    STOP
297902 PRINT*,'+++ unexpected end on file "', TRIM( filename(2) ), '"'
298    PRINT*,'    while reading indices'
299    STOP
300903 PRINT*,'+++ unexpected end on file "', TRIM( filename(1) ), '"'
301    PRINT*,'    while reading array data'
302    STOP
303904 PRINT*,'+++ unexpected end on file "', TRIM( filename(2) ), '"'
304    PRINT*,'    while reading array data'
305    STOP
306
307 END PROGRAM compare_palm_logs
308
309
310
Note: See TracBrowser for help on using the repository browser.