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

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

last commit documented / added nc2vdf

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