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

Last change on this file since 1046 was 1046, checked in by maronga, 11 years ago

put scripts and utilities under GPL

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