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

Last change on this file since 1482 was 1469, checked in by maronga, 10 years ago

last commit documented

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