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

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

preprocessor directives using machine dependent flags (lc, ibm, etc.) mostly removed from the code

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