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

Last change on this file since 4418 was 4274, checked in by raasch, 4 years ago

bugfix for processing data from atmosphere-ocean coupled runs (only atmosphere data were processed, but twice)

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