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

Last change on this file since 691 was 691, checked in by maronga, 13 years ago

Bugfix for precursor atmosphere/ocean runs, re-adjustments for lcxt4

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