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

Last change on this file since 2543 was 2523, checked in by kanani, 7 years ago

Added .palm.config.idefix, and bugfix in combine_plot_fields

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