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

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

Vertical nesting implemented (SadiqHuq?)

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