source: palm/trunk/UTIL/combine_plot_fields.f90 @ 1823

Last change on this file since 1823 was 1809, checked in by raasch, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 31.1 KB
Line 
1 PROGRAM combine_plot_fields
2
3!------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2014  Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: combine_plot_fields.f90 1809 2016-04-05 20:13:28Z hoffmann $
27!
28! 1808 2016-04-05 19:44:00Z raasch
29! cpu measurements are done with standard FORTRAN routine on every machine
30!
31! 1551 2015-03-03 14:18:16Z maronga
32! Adjustments for data output of soil model quantities
33!
34! 1468 2014-09-24 14:06:57Z maronga
35! Adapted for use on up to 6-digit processor cores (not tested)
36!
37! 1394 2014-05-06 10:17:31Z keck
38! KIND-attribute added to all INTEGER and REAL declaration statements
39!
40! 1046 2012-11-09 14:38:45Z maronga
41! code put under GPL (PALM 3.9)
42!
43! 691 2011-03-04 08:45:30Z maronga
44! Bugfix: check for precursor ocean runs, removed typo
45!
46! 493 2010-03-01 08:30:24Z raasch
47! Exit in case of already complete NetCDF data (due to parallel output in PALM)
48! cpu measurements included
49!
50! 210 2008-11-06 08:54:02Z raasch
51! Size of pf3d adjusted to the required output size (1 gridpoint less, along
52! all three dimensions), because output of a subset of the data
53! (pf3d(nxa:nxe...) in the NF90_PUT_VAR statement caused segmentation fault
54! with the INTEL compiler.
55! Subdomain data are read into temporary arrays pf_tmp/pf3d_tmp in order to
56! avoid INTEL compiler warnings about (automatic) creation of temporary arrays
57! Bugfix: three misplaced #endif directives
58!
59! 114 2007-10-10 00:03:15Z raasch
60! Bugfix: model_string needed a default value
61!
62! Aug 07    Loop for processing of output by coupled runs, id_string does not
63!           contain modus any longer
64!
65! 18/01/06  Output of time-averaged data
66!
67! 25/05/05  Errors removed
68!
69! 26/04/05  Output in NetCDF format, iso2d and avs output only if parameter
70!           file exists
71!
72! 31/10/01  All comments and messages translated into English
73!
74! 23/02/99  Keine Bearbeitung komprimierter 3D-Daten
75! Ursprungsversion vom 28/07/97
76!
77!
78! Description:
79! ------------
80! This routine combines data of the PALM-subdomains into one file. In PALM
81! every processor element opens its own file and writes 2D- or 3D-binary-data
82! into it (different files are opened for xy-, xz-, yz-cross-sections and
83! 3D-data). For plotting or analyzing these PE-data have to be collected and
84! to be put into single files, which is done by this routine.
85! Output format is NetCDF. Additionally, a data are output in a binary format
86! readable by ISO2D-software (cross-sections) and by AVS (3D-data).
87!------------------------------------------------------------------------------!
88
89#if defined( __netcdf )
90    USE netcdf
91#endif
92
93    IMPLICIT NONE
94
95!
96!-- Local variables
97    CHARACTER (LEN=2)    ::  modus, model_string
98    CHARACTER (LEN=6)    ::  id_string
99    CHARACTER (LEN=20)   ::  dimname, var_name
100    CHARACTER (LEN=40)   ::  filename
101
102    CHARACTER (LEN=2000), DIMENSION(0:1) ::  var_list
103
104    INTEGER, PARAMETER ::  iwp = 4, spk = SELECTED_REAL_KIND( 6 ), wp = 8
105
106    INTEGER(iwp) ::  av, danz, i, id, j, k, model, models, nc_stat,            &
107                     nxa, nxag, nxe, nxeg, nya, nyag, nye, nyeg,               &
108                     nza, nze, pos, time_step,                                 &
109                     xa, xe, xxa, xxe, ya, ya_do, ya_tot, ye, ye_do, ye_tot, yya, yye, za,   &
110                     ze, zza, zze
111
112    INTEGER(8)                        ::  count, count_rate
113
114    INTEGER(iwp), DIMENSION(0:1)      ::  current_level, current_var,          &
115                                          fanz, id_set, id_var_time, num_var
116    INTEGER(iwp), DIMENSION(4)        ::  id_dims_loc
117    INTEGER(iwp), DIMENSION(0:1,4)    ::  id_dims
118    INTEGER(iwp), DIMENSION(0:1,1000) ::  id_var, levels
119
120    LOGICAL  ::  avs_output, compressed, found, iso2d_output, netcdf_output,   &
121                 netcdf_parallel, netcdf_0, netcdf_1
122
123    REAL(wp) ::  cpu_start_time, cpu_end_time, dx, simulated_time
124    REAL(wp),  DIMENSION(:),   ALLOCATABLE   ::  eta, ho, hu
125    REAL(wp),  DIMENSION(:,:), ALLOCATABLE   ::  pf, pf_tmp
126    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE ::  pf3d, pf3d_tmp
127
128    PRINT*, ''
129    PRINT*, ''
130    PRINT*, '*** combine_plot_fields ***'
131
132!
133!-- Find out if a coupled run has been carried out
134    INQUIRE( FILE='COUPLING_PORT_OPENED', EXIST=found )
135    IF ( found )  THEN
136       models = 2
137       PRINT*, '    coupled run'
138    ELSE
139       models = 1
140       PRINT*, '    uncoupled run'
141    ENDIF
142
143!
144!-- Find out if a precursor ocean run has been carried out
145    INQUIRE( FILE='PRECURSOR_OCEAN', EXIST=found )
146    IF ( found )  THEN
147       model_string = '_O'
148       PRINT*, '    precursor ocean run'
149    ELSE
150       model_string = ''
151    ENDIF
152
153!
154!-- Do everything for each model
155    DO model = 1, models
156!
157!--    Set the model string used to identify the filenames
158       IF ( models == 2 )  THEN
159          PRINT*, ''
160          PRINT*, '*** combine_plot_fields ***'
161          IF ( model == 2 )  THEN
162             model_string = '_O'
163             PRINT*, '    now combining ocean data'
164             PRINT*, '    ========================'
165          ELSE
166             PRINT*, '    now combining atmosphere data'
167             PRINT*, '    ============================='
168          ENDIF
169       ENDIF
170!
171!--    2D-arrays for ISO2D
172!--    Main loop for the three different cross-sections, starting with
173!--    xy-section
174       modus = 'XY'
175       PRINT*, ''
176       DO  WHILE ( modus == 'XY'  .OR.  modus == 'XZ'  .OR.  modus == 'YZ' )
177!
178!--       Take current time
179          CALL SYSTEM_CLOCK( count, count_rate )
180          cpu_start_time = REAL( count ) / REAL( count_rate )
181
182          netcdf_parallel = .FALSE.
183!
184!--       Check, if file from PE0 exists. If it does not exist, PALM did not
185!--       create any output for this cross-section.
186          danz = 0
187          WRITE (id_string,'(I6.6)')  danz
188          INQUIRE ( &
189               FILE='PLOT2D_'//modus//TRIM( model_string )//'_'//id_string, &
190               EXIST=found )
191!
192!--       Find out the number of files (equal to the number of PEs which
193!--       have been used in PALM) and open them
194          DO  WHILE ( found )
195
196             OPEN ( danz+110, &
197                  FILE='PLOT2D_'//modus//TRIM( model_string )//'_'//id_string, &
198                  FORM='UNFORMATTED' )
199             danz = danz + 1
200             WRITE (id_string,'(I6.6)')  danz
201             INQUIRE ( &
202                  FILE='PLOT2D_'//modus//TRIM( model_string )//'_'//id_string, &
203                  EXIST=found )
204
205          ENDDO
206
207!
208!--       Inquire whether an iso2d parameter file exists
209          INQUIRE( FILE='PLOT2D_'//modus//'_GLOBAL'//TRIM( model_string ), &
210               EXIST=iso2d_output )
211
212!
213!--       Inquire whether a NetCDF file exists
214          INQUIRE( FILE='DATA_2D_'//modus//'_NETCDF'//TRIM( model_string ), &
215               EXIST=netcdf_0 )
216
217!
218!--       Inquire whether a NetCDF file for time-averaged data exists
219          INQUIRE( FILE='DATA_2D_'//modus//'_AV_NETCDF'//TRIM( model_string ),&
220               EXIST=netcdf_1 )
221
222          IF ( netcdf_0  .OR.  netcdf_1 )  THEN
223             netcdf_output = .TRUE.
224!
225!--          Inquire whether the NetCDF file is already complete (parallel
226!--          output)
227             INQUIRE( FILE='NO_COMBINE_PLOT_FIELDS_'//modus, &
228                      EXIST=netcdf_parallel )
229             IF ( netcdf_parallel )  THEN
230                netcdf_parallel = .TRUE.
231             ELSE
232                netcdf_parallel = .FALSE.
233             ENDIF
234          ELSE
235             netcdf_output = .FALSE.
236          ENDIF
237
238!
239!--       Info-output
240          PRINT*, ''
241          PRINT*, '*** combine_plot_fields ***'
242#if defined( __netcdf )
243          IF ( netcdf_output )  THEN
244             IF ( netcdf_parallel )  THEN
245             PRINT*, '    NetCDF ' // modus // '-data are in one file ', &
246                          '(NetCDF4-format) - merging not neccessary'
247             ELSE
248                PRINT*, '    NetCDF output enabled'
249             ENDIF
250          ENDIF
251#else
252          IF ( netcdf_output )  THEN
253             PRINT*, '--- Sorry, no NetCDF support on this host'
254             netcdf_output = .FALSE.
255          ENDIF
256#endif
257          IF ( .NOT. netcdf_parallel )  THEN
258             IF ( danz /= 0 )  THEN
259                PRINT*, '    ',modus,'-section:  ', danz, ' file(s) found'
260             ELSE
261                PRINT*, '    no ', modus, '-section data available'
262             ENDIF
263          ENDIF
264
265          IF ( netcdf_output  .AND. .NOT. netcdf_parallel  .AND.  danz /= 0 ) &
266          THEN
267#if defined( __netcdf )
268             DO  av = 0, 1
269
270                IF ( av == 0  .AND.  .NOT.  netcdf_0 )  CYCLE
271                IF ( av == 1  .AND.  .NOT.  netcdf_1 )  CYCLE
272
273!
274!--             Open NetCDF dataset
275                IF ( av == 0 )  THEN
276                   filename = 'DATA_2D_'//modus//'_NETCDF' &
277                        //TRIM( model_string )
278                ELSE
279                   filename = 'DATA_2D_'//modus//'_AV_NETCDF' &
280                        //TRIM( model_string )
281                ENDIF
282                nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set(av) )
283                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 1 )
284
285!
286!--             Get the list of variables (order of variables corresponds with
287!--             the order of data on the binary file)
288                var_list(av) = ' '    ! GET_ATT does not assign trailing blanks
289                nc_stat = NF90_GET_ATT( id_set(av), NF90_GLOBAL, 'VAR_LIST', &
290                     var_list(av) )
291                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 2 )
292
293!
294!--             Inquire id of the time coordinate variable
295                nc_stat = NF90_INQ_VARID( id_set(av), 'time', id_var_time(av) )
296                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 3 )
297
298!
299!--             Count number of variables; there is one more semicolon in the
300!--             string than variable names
301                num_var(av) = -1
302                DO  i = 1, LEN( var_list(av) )
303                   IF ( var_list(av)(i:i) == ';' )  num_var(av) = num_var(av) +1
304                ENDDO
305
306!
307!--             Extract the variable names from the list and inquire their
308!--             NetCDF IDs
309                pos = INDEX( var_list(av), ';' )
310!
311!--             Loop over all variables
312                DO  i = 1, num_var(av)
313
314!
315!--                Extract variable name from list
316                   var_list(av) = var_list(av)(pos+1:)
317                   pos = INDEX( var_list(av), ';' )
318                   var_name = var_list(av)(1:pos-1)
319
320!
321!--                Get variable ID from name
322                   nc_stat = NF90_INQ_VARID( id_set(av), TRIM( var_name ), &
323                        id_var(av,i) )
324                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 4 )
325
326!
327!--                Get number of x/y/z levels for that variable
328                   nc_stat = NF90_INQUIRE_VARIABLE( id_set(av), id_var(av,i), &
329                        dimids = id_dims_loc )
330                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 5 )
331                   id_dims(av,:) = id_dims_loc
332
333!
334!--                Inquire dimension ID
335                   DO  j = 1, 4
336                      nc_stat = NF90_INQUIRE_DIMENSION( id_set(av), &
337                           id_dims(av,j), dimname, levels(av,i) )
338                      IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 6 )
339
340                      IF ( modus == 'XY' .AND. INDEX(dimname, 'z') /= 0 )  EXIT
341                      IF ( modus == 'XZ' .AND. INDEX(dimname, 'y') /= 0 )  EXIT
342                      IF ( modus == 'YZ' .AND. INDEX(dimname, 'x') /= 0 )  EXIT
343                   ENDDO
344
345                ENDDO
346
347             ENDDO   ! av = 0, 1
348
349#endif
350          ENDIF
351
352!
353!--       Read the arrays, as long as the end of the file is reached
354          IF ( .NOT. netcdf_parallel )  THEN
355
356             fanz          =         0
357             current_level =         1
358             current_var   = 999999999
359
360             DO  WHILE ( danz /= 0 )
361
362!
363!--             Loop over all files (reading data of the subdomains)
364                DO  id = 0, danz-1
365!
366!--                File from PE0 contains special information at the beginning,
367!--                concerning the lower and upper indices of the total-domain
368!--                used in PALM (nxag, nxeg, nyag, nyeg) and the lower and
369!--                upper indices of the array to be written by this routine
370!--                (nxa, nxe, nya, nye). Usually in the horizontal directions
371!--                nxag=-1 and nxa=0 while all other variables have the same
372!--                value (i.e. nxeg=nxe).
373!--                Allocate necessary arrays, open the output file and write
374!--                the coordinate informations needed by ISO2D.
375                   IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 ) THEN
376                      READ ( id+110 )  nxag, nxeg, nyag, nyeg
377                      READ ( id+110 )  nxa, nxe, nya, nye
378                      ALLOCATE ( eta(nya:nye), ho(nxa:nxe), hu(nxa:nxe), &
379                                 pf(nxag:nxeg,nyag:nyeg) )
380                      READ ( id+110 )  dx, eta, hu, ho
381
382
383!
384!--                   Set actual domain bounds to total domain
385                      ya_do = nya
386                      ye_do = nye
387
388                      IF ( iso2d_output )  THEN
389                         OPEN ( 2, FILE='PLOT2D_'//modus//TRIM( model_string ),&
390                                   FORM='UNFORMATTED' )
391                         WRITE ( 2 )  dx, eta, hu, ho
392                      ENDIF
393                   ENDIF
394!
395!--                Read output time
396                   IF ( netcdf_output  .AND.  id == 0 )  THEN
397                      IF ( netcdf_1 )  THEN
398                         READ ( id+110, END=998 )  simulated_time, time_step, av
399                      ELSE
400!
401!--                      For compatibility with earlier PALM versions
402                         READ ( id+110, END=998 )  simulated_time, time_step
403                         av = 0
404                      ENDIF
405                   ENDIF
406!
407!--                Read subdomain indices
408                   READ ( id+110, END=998 )  xa, xe, ya, ye, ya_tot, ye_tot
409
410!
411!--                IF the PE made no output (in case that no part of the
412!--                cross-section is situated on this PE), indices have the
413!--                value -1
414                   IF ( .NOT. ( xa == -1  .AND.  xe == -1  .AND. &
415                                ya == -1  .AND.  ye == -1 ) )  THEN
416
417
418!
419!--                   Read the subdomain grid-point values
420                      ALLOCATE( pf_tmp(xa:xe,ya:ye) )
421                      READ ( id+110 )  pf_tmp
422!
423!--                   Calculate indices on atmospheric grid (e.g. for soil model
424!--                   quantities)
425                      IF ( ya /= ya_tot .OR. ye /= ye_tot )  THEN
426                         ye_do = ye - ya
427                         ya_do = ya
428                         pf(xa:xe,ya_do:ye_do) = pf_tmp
429                      ELSE
430                         ye_do = nye
431                         ya_do = nya
432                         pf(xa:xe,ya:ye) = pf_tmp
433                      ENDIF
434
435                      DEALLOCATE( pf_tmp )
436                   ENDIF
437                   IF ( id == 0 )  fanz(av) = fanz(av) + 1
438
439                ENDDO
440!
441!--             Write the data of the total domain cross-section
442                IF ( iso2d_output )  WRITE ( 2 )  pf(nxa:nxe,nya:nye)
443       
444!
445!--             Write same data in NetCDF format
446                IF ( netcdf_output )  THEN
447#if defined( __netcdf )
448!
449!--                Check if a new time step has begun; if yes write data to
450!--                time axis
451                   IF ( current_var(av) > num_var(av) )  THEN
452                      current_var(av) = 1
453                      nc_stat = NF90_PUT_VAR( id_set(av), id_var_time(av), &
454                                              (/ simulated_time /),        &
455                                              start = (/ time_step /),     &
456                                              count = (/ 1 /) )
457                      IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 7 )
458                   ENDIF
459
460!
461!--                Now write the data; this is mode dependent
462                   SELECT CASE ( modus )
463
464                      CASE ( 'XY' )
465                         nc_stat = NF90_PUT_VAR( id_set(av),                   &
466                                           id_var(av,current_var(av)),         &
467                                           pf(nxa:nxe,nya:nye),                &
468                             start = (/ 1, 1, current_level(av), time_step /), &
469                                      count = (/ nxe-nxa+1, nye-nya+1, 1, 1 /) )
470                         IF ( nc_stat /= NF90_NOERR )  THEN
471                            CALL handle_netcdf_error( 8 )
472                         ENDIF
473                 
474                      CASE ( 'XZ' )
475                         nc_stat = NF90_PUT_VAR( id_set(av),                   &
476                                           id_var(av,current_var(av)),         &
477                                           pf(nxa:nxe,ya_do:ye_do),            &
478                             start = (/ 1, current_level(av), 1, time_step /), &
479                                      count = (/ nxe-nxa+1, 1, ye_do-ya_do+1, 1 /) )
480                         IF ( nc_stat /= NF90_NOERR )  THEN
481                            CALL handle_netcdf_error( 9 )
482                         ENDIF
483
484                      CASE ( 'YZ' )
485                         nc_stat = NF90_PUT_VAR( id_set(av),                   &
486                                           id_var(av,current_var(av)),         &
487                                           pf(nxa:nxe,ya_do:ye_do),            &
488                             start = (/ current_level(av), 1, 1, time_step /), &
489                                      count = (/ 1, nxe-nxa+1, ye_do-ya_do+1, 1 /) )
490                         IF ( nc_stat /= NF90_NOERR )  THEN
491                            CALL handle_netcdf_error( 10 )
492                         ENDIF
493
494                   END SELECT
495
496!
497!--                Data is written, check if max level is reached
498                   current_level(av) = current_level(av) + 1
499                   IF ( current_level(av) > levels(av,current_var(av)) )  THEN
500                      current_level(av) = 1
501                      current_var(av)   = current_var(av) + 1
502                   ENDIF
503
504#endif
505                ENDIF
506
507             ENDDO
508
509          ENDIF
510
511998       IF ( danz /= 0  .AND.  .NOT. netcdf_parallel )  THEN
512!
513!--          Print the number of the arrays processed
514             WRITE (*,'(16X,I4,A)')  fanz(0)+fanz(1), ' array(s) processed'
515             IF ( fanz(1) /= 0 )  THEN
516                WRITE (*,'(16X,I4,A)')  fanz(1), ' array(s) are time-averaged'
517             ENDIF
518
519!
520!--          Close all files and deallocate arrays
521             DO  id = 0, danz-1
522                CLOSE ( id+110 )
523             ENDDO
524             CLOSE ( 2 )
525             DEALLOCATE ( eta, ho, hu, pf )
526
527!
528!--          Close the NetCDF file
529             IF ( netcdf_output )  THEN
530#if defined( __netcdf )
531                IF ( netcdf_0 )  THEN
532                   nc_stat = NF90_CLOSE( id_set(0) )
533                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 11 )
534                ENDIF
535                IF ( netcdf_1 )  THEN
536                   nc_stat = NF90_CLOSE( id_set(1) )
537                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 12 )
538                ENDIF
539#endif
540             ENDIF
541          ENDIF
542
543!
544!--       Output required cpu time
545          IF ( danz /= 0  .AND.  .NOT. netcdf_parallel )  THEN
546             CALL SYSTEM_CLOCK( count, count_rate )
547             cpu_end_time = REAL( count ) / REAL( count_rate )
548             WRITE (*,'(5X,A,F9.3,A)')  'Required cpu-time: ', &
549                                        cpu_end_time-cpu_start_time, ' sec'
550          ENDIF
551
552!
553!--       Choose the next cross-section
554          SELECT CASE ( modus )
555             CASE ( 'XY' )
556                modus = 'XZ'
557             CASE ( 'XZ' )
558                modus = 'YZ'
559             CASE ( 'YZ' )
560                modus = 'no'
561          END SELECT
562
563       ENDDO
564
565
566!
567!--    Combine the 3D-arrays
568       netcdf_parallel = .FALSE.
569
570!
571!--    Info-output
572       PRINT*, ' '
573       PRINT*, '*** combine_plot_fields ***'
574
575!
576!--    Take current time
577       CALL SYSTEM_CLOCK( count, count_rate )
578       cpu_start_time = REAL( count ) / REAL( count_rate )
579
580!
581!--    Inquire whether an avs fld file exists
582       INQUIRE( FILE='PLOT3D_FLD'//TRIM( model_string ), EXIST=avs_output )
583
584!
585!--    Inquire whether a NetCDF file exists
586       INQUIRE( FILE='DATA_3D_NETCDF'//TRIM( model_string ), EXIST=netcdf_0 )
587
588!
589!--    Inquire whether a NetCDF file for time-averaged data exists
590       INQUIRE( FILE='DATA_3D_AV_NETCDF'//TRIM( model_string ), EXIST=netcdf_1 )
591
592       IF ( netcdf_0  .OR.  netcdf_1 )  THEN
593          netcdf_output = .TRUE.
594!
595!--       Inquire whether the NetCDF file is already complete (parallel output)
596          INQUIRE( FILE='NO_COMBINE_PLOT_FIELDS_3D', EXIST=netcdf_parallel )
597          IF ( netcdf_parallel )  THEN
598             netcdf_parallel = .TRUE.
599          ELSE
600             netcdf_parallel = .FALSE.
601          ENDIF
602       ELSE
603          netcdf_output = .FALSE.
604       ENDIF
605
606!
607!--    Check, if file from PE0 exists; not neccessary in case of parallel
608!--    PALM output
609       IF ( .NOT. netcdf_parallel )  THEN
610          danz = 0
611          WRITE (id_string,'(I6.6)')  danz
612          INQUIRE ( &
613               FILE='PLOT3D_DATA'//TRIM( model_string )//'_'//TRIM( id_string ),  &
614               EXIST=found )
615       ELSE
616          found = .FALSE.
617       ENDIF
618
619!
620!--    Combination only works, if data are not compressed. In that case,
621!--    PALM created a flag file (PLOT3D_COMPRESSED)
622       INQUIRE ( FILE='PLOT3D_COMPRESSED'//TRIM( model_string ), &
623            EXIST=compressed )
624
625!
626!--    Find out the number of files and open them
627       DO  WHILE ( found  .AND.  .NOT. compressed )
628
629          OPEN ( danz+110, &
630               FILE='PLOT3D_DATA'//TRIM( model_string )//'_'//TRIM(id_string), &
631               FORM='UNFORMATTED')
632          danz = danz + 1
633          WRITE (id_string,'(I6.6)')  danz
634          INQUIRE ( &
635               FILE='PLOT3D_DATA'//TRIM( model_string )//'_'//TRIM(id_string), &
636               EXIST=found )
637
638       ENDDO
639
640#if defined( __netcdf )
641       IF ( netcdf_output )  THEN
642          IF ( netcdf_parallel )  THEN
643             PRINT*, '    NetCDF data are in one file (NetCDF4-format)', &
644                          ' - merging not neccessary'
645          ELSE
646             PRINT*, '    NetCDF output enabled'
647          ENDIF
648       ENDIF
649#else
650       IF ( netcdf_output )  THEN
651          PRINT*, '--- Sorry, no NetCDF support on this host'
652          netcdf_output = .FALSE.
653       ENDIF
654#endif
655       IF ( .NOT. netcdf_parallel )  THEN
656          IF ( danz /= 0 )  THEN
657             PRINT*, '    3D-data:     ', danz, ' file(s) found'
658          ELSE
659             IF ( found .AND. compressed )  THEN
660                PRINT*, '+++ no 3D-data processing, since data are compressed'
661             ELSE
662                PRINT*, '    no 3D-data file available'
663             ENDIF
664          ENDIF
665       ENDIF
666
667       IF ( netcdf_output  .AND. .NOT. netcdf_parallel  .AND.  danz /= 0 )  THEN
668#if defined( __netcdf )
669          DO  av = 0, 1
670
671             IF ( av == 0  .AND.  .NOT.  netcdf_0 )  CYCLE
672             IF ( av == 1  .AND.  .NOT.  netcdf_1 )  CYCLE
673
674!
675!--          Open NetCDF dataset
676             IF ( av == 0 )  THEN
677                filename = 'DATA_3D_NETCDF'//TRIM( model_string )
678             ELSE
679                filename = 'DATA_3D_AV_NETCDF'//TRIM( model_string )
680             ENDIF
681             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set(av) )
682             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 13 )
683
684
685!
686!--          Get the list of variables (order of variables corresponds with the
687!--          order of data on the binary file)
688             var_list(av) = ' '    ! GET_ATT does not assign trailing blanks
689             nc_stat = NF90_GET_ATT( id_set(av), NF90_GLOBAL, 'VAR_LIST', &
690                  var_list(av) )
691             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 14 )
692
693!
694!--          Inquire id of the time coordinate variable
695             nc_stat = NF90_INQ_VARID( id_set(av), 'time', id_var_time(av) )
696             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 15 )
697
698!
699!--          Count number of variables; there is one more semicolon in the
700!--          string than variable names
701             num_var(av) = -1
702             DO  i = 1, LEN( var_list(av) )
703                IF ( var_list(av)(i:i) == ';' )  num_var(av) = num_var(av) + 1
704             ENDDO
705
706!
707!--          Extract the variable names from the list and inquire their NetCDF
708!--          IDs
709             pos = INDEX( var_list(av), ';' )
710!
711!--          Loop over all variables
712             DO  i = 1, num_var(av)
713
714!
715!--             Extract variable name from list
716                var_list(av) = var_list(av)(pos+1:)
717                pos = INDEX( var_list(av), ';' )
718                var_name = var_list(av)(1:pos-1)
719
720!
721!--             Get variable ID from name
722                nc_stat = NF90_INQ_VARID( id_set(av), TRIM( var_name ), &
723                     id_var(av,i) )
724                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 16 )
725
726             ENDDO
727
728          ENDDO    ! av=0,1
729
730#endif
731       ENDIF
732
733!
734!--    Read arrays, until the end of the file is reached
735       IF ( .NOT. netcdf_parallel )  THEN
736
737          current_var = 999999999
738          fanz = 0
739          DO  WHILE ( danz /= 0 )
740
741!
742!--          Loop over all files
743             DO  id = 0, danz-1
744!
745!--             File from PE0 contains special information at the beginning,
746!--             concerning the lower and upper indices of the total-domain used
747!--             in PALM (nxag, nxeg, nyag, nyeg) and the lower and
748!--             upper indices of the array to be written by this routine (nxa,
749!--             nxe, nya, nye, nza, nze). Usually nxag=-1 and nxa=0, nyag=-1
750!--             and nya=0, nzeg=nz and nze=nz_do3d.
751!--             Allocate necessary array and open the output file.
752                IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 )  THEN
753                   READ ( id+110 )  nxag, nxeg, nyag, nyeg
754                   READ ( id+110 )  nxa, nxe, nya, nye, nza, nze
755                   ALLOCATE ( pf3d(nxa:nxe,nya:nye,nza:nze) )
756                   IF ( avs_output )  THEN
757                      OPEN ( 2, FILE='PLOT3D_DATA'//TRIM( model_string ), &
758                             FORM='UNFORMATTED' )
759                   ENDIF
760                ENDIF
761
762!
763!--             Read output time
764                IF ( netcdf_output  .AND.  id == 0 )  THEN
765                   IF ( netcdf_1 )  THEN
766                      READ ( id+110, END=999 )  simulated_time, time_step, av
767                   ELSE
768!
769!--                   For compatibility with earlier PALM versions
770                      READ ( id+110, END=999 )  simulated_time, time_step
771                      av = 0
772                   ENDIF
773                ENDIF
774
775!
776!--             Read subdomain indices and grid point values
777                READ ( id+110, END=999 )  xa, xe, ya, ye, za, ze
778                ALLOCATE( pf3d_tmp(xa:xe,ya:ye,za:ze) )
779                READ ( id+110 )  pf3d_tmp
780
781                xxa = MAX( nxa, xa )
782                xxe = MIN( nxe, xe )
783                yya = MAX( nya, ya )
784                yye = MIN( nye, ye )
785                DO  k = za, ze
786                   DO  j = yya, yye
787                      DO  i = xxa, xxe
788                         pf3d(i,j,k) = pf3d_tmp(i,j,k)
789                      ENDDO
790                   ENDDO
791                ENDDO
792
793                DEALLOCATE( pf3d_tmp )
794                IF ( id == 0 )  fanz(av) = fanz(av) + 1
795
796             ENDDO
797
798!
799!--          Write data of the total domain
800             IF ( avs_output )  WRITE ( 2 )  pf3d(nxa:nxe,nya:nye,nza:nze)
801       
802!
803!--          Write same data in NetCDF format
804             IF ( netcdf_output )  THEN
805#if defined( __netcdf )
806!
807!--             Check if a new time step has begun; if yes write data to time
808!--             axis
809                IF ( current_var(av) > num_var(av) )  THEN
810                   current_var(av) = 1
811                   nc_stat = NF90_PUT_VAR( id_set(av), id_var_time(av), &
812                                      (/ simulated_time /),&
813                                      start = (/ time_step /), count = (/ 1 /) )
814                   IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 17 )
815                ENDIF
816
817!
818!--             Now write the data
819                nc_stat = NF90_PUT_VAR( id_set(av), id_var(av,current_var(av)),&
820                                        pf3d(nxa:nxe,nya:nye,za:ze), start = (/ 1, 1, 1, time_step /),&
821                              count = (/ nxe-nxa+1, nye-nya+1, ze-za+1, 1 /) )
822                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 18 )
823
824                current_var(av) = current_var(av) + 1
825
826#endif
827             ENDIF
828
829          ENDDO
830
831       ENDIF
832
833999    IF ( danz /= 0  .AND.  .NOT. netcdf_parallel )  THEN
834!
835!--       Print the number of arrays processed
836          WRITE (*,'(16X,I4,A)')  fanz(0)+fanz(1), ' array(s) processed'
837          IF ( fanz(1) /= 0 )  THEN
838             WRITE (*,'(16X,I4,A)')  fanz(1), ' array(s) are time-averaged'
839          ENDIF
840!
841!--       Close all files and deallocate array
842          DO  id = 0, danz-1
843             CLOSE ( id+110 )
844          ENDDO
845          CLOSE ( 2 )
846          DEALLOCATE ( pf3d )
847!
848!--       Close the NetCDF file
849          IF ( netcdf_output )  THEN
850#if defined( __netcdf )
851             IF ( netcdf_0 )  THEN
852                nc_stat = NF90_CLOSE( id_set(0) )
853                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 19 )
854             ENDIF
855             IF ( netcdf_1 )  THEN
856                nc_stat = NF90_CLOSE( id_set(1) )
857                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 20 )
858             ENDIF
859#endif
860          ENDIF
861
862!
863!--       Output required cpu time
864          CALL SYSTEM_CLOCK( count, count_rate )
865          cpu_end_time = REAL( count ) / REAL( count_rate )
866          WRITE (*,'(5X,A,F9.3,A)')  'Required cpu-time: ', &
867                                     cpu_end_time-cpu_start_time, ' sec'
868
869       ENDIF
870
871    ENDDO  ! models
872
873
874 CONTAINS
875
876
877    SUBROUTINE handle_netcdf_error( errno )
878!
879!--    Prints out a text message corresponding to the current NetCDF status
880
881       IMPLICIT NONE
882
883       INTEGER, INTENT(IN) ::  errno
884
885#if defined( __netcdf )
886       IF ( nc_stat /= NF90_NOERR )  THEN
887          PRINT*, '+++ combine_plot_fields  netcdf: ', av, errno, &
888                  TRIM( nf90_strerror( nc_stat ) )
889       ENDIF
890#endif
891
892    END SUBROUTINE handle_netcdf_error
893
894
895 END PROGRAM combine_plot_fields
896
897
898
Note: See TracBrowser for help on using the repository browser.