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

Last change on this file since 493 was 493, checked in by raasch, 14 years ago

New:
---
Output in NetCDF4-format. New d3par-parameter netcdf_data_format.

(check_open, check_parameters, close_file, data_output_2d, data_output_3d, header, modules, netcdf, parin)

Modules to be loaded for compilation (mbuild) or job execution (mrun)
can be given in the configuration file using variable modules. Example:

%modules ifort/11.0.069:netcdf lcsgih parallel

This method replaces the (undocumented) mpilib-variable.

WARNING: All fixed settings of modules in the scripts mbuild, mrun, and subjob
have been removed! Please set the modules variable appropriately in your
configuration file. (mbuild, mrun, subjob)

Changed:


Parameters netcdf_64bit and netcdf_64bit_3d have been removed. Use
netcdf_data_format = 2 for choosing the classic 64bit-offset format (this is
the default). The offset-format can not be set independently for the
3d-output-data any more.

Parameters netcdf_format_mask, netcdf_format_mask_av, and variables
nc_format_mask, format_parallel_io removed. They are replaced by the new
parameter netcdf_data_format. (check_open, close_file,
data_output_mask, header, init_masks, modules, parin)

Errors:


bugfix in trunk/UTIL/Makefile: forgot to compile for interpret_config

Bugfix: timeseries data have to be collected by PE0 (user_statistics)

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