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

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

land surface model released

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