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

Last change on this file since 818 was 692, checked in by maronga, 13 years ago

last commit documented

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