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

Last change on this file since 1787 was 1552, checked in by maronga, 9 years ago

last commit documented

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