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

Last change on this file since 2696 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

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