source: palm/trunk/UTIL/inifor/src/inifor.f90 @ 4807

Last change on this file since 4807 was 4756, checked in by eckhard, 4 years ago

inifor: Fixed an error in surface pressure extrapolation

  • Property svn:keywords set to Id
File size: 27.7 KB
RevLine 
[2696]1!> @file src/inifor.f90
2!------------------------------------------------------------------------------!
[2718]3! This file is part of the PALM model system.
[2696]4!
[2718]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
[2696]8! version.
9!
[2718]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.
[2696]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!
[4481]17! Copyright 2017-2020 Leibniz Universitaet Hannover
18! Copyright 2017-2020 Deutscher Wetterdienst Offenbach
[2696]19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
[4659]23!
24!
[3183]25! Former revisions:
26! -----------------
27! $Id: inifor.f90 4756 2020-10-26 10:05:58Z gronemeier $
[4756]28! Improved variable naming and code readabilty
29!
30!
31! 4675 2020-09-11 10:00:26Z eckhard
[4675]32! Support for soil profile initialization
33! Improved code formatting
34!
35!
36! 4659 2020-08-31 11:21:17Z eckhard
[4659]37! List all warnings after successful run
38! Only define netCDF variables in enabled IO groups
39!
40!
41! 4523 2020-05-07 15:58:16Z eckhard
[4523]42! respect integer working precision (iwp) specified in inifor_defs.f90
43!
44!
45! 4481 2020-03-31 18:55:54Z maronga
[3997]46! Alert user to warnings if any
47!
48!
49! 3866 2019-04-05 14:25:01Z eckhard
[3866]50! Use PALM's working precision
51! Show error message if compiled without netCDF support
52! Renamed run_control -> log_runtime
53! Improved coding style added comments
54!
55!
56! 3785 2019-03-06 10:41:14Z eckhard
[3779]57! Average geostrophic wind components on coarse COSMO levels instead of fine PALM levels
58! Remove --debug netCDF output of internal pressure profiles
59!
60! 3680 2019-01-18 14:54:12Z knoop
[3618]61! Prefixed all INIFOR modules with inifor_
62!
63!
64! 3615 2018-12-10 07:21:03Z raasch
[3615]65! bugfix: abort replaced by inifor_abort
66!
67! 3613 2018-12-07 18:20:37Z eckhard
[3613]68! Moved version output to setup_parameters()
69!
70! 3557 2018-11-22 16:01:22Z eckhard
[3557]71! Updated documentation
72!
73! 3537 2018-11-20 10:53:14Z eckhard
[3537]74! Print version number on program start
75!
76!
77! 3456 2018-10-30 14:29:54Z eckhard
[3456]78! NetCDf output of internal arrays only with --debug option
79!
80!
81! 3401 2018-10-23 09:33:31Z eckhard
[3401]82! Re-compute geostrophic winds every time step
83!
84! 3395 2018-10-22 17:32:49Z eckhard
[3395]85! Added main loop support for computation of geostrophic winds and surface
86!     pressure
87! Cleaned up terminal output, show some meVssages only with --debug option
88!
89! 3183 2018-07-27 14:25:55Z suehring
[3182]90! Introduced new PALM grid stretching
91! Renamend initial-condition mode variable 'mode' to 'ic_mode'
92! Improved log messages
[2696]93!
94!
[3183]95! 3182 2018-07-27 13:36:03Z suehring
[2696]96! Initial revision
97!
98!
99!
100! Authors:
101! --------
[3557]102!> @author Eckhard Kadasch, (Deutscher Wetterdienst, Offenbach)
[2696]103!
104! Description:
105! ------------
106!> INIFOR is an interpolation tool for generating meteorological initialization
107!> and forcing data for the urban climate model PALM-4U. The required
108!> meteorological fields are interpolated from output data of the mesoscale
[3779]109!> model COSMO. This is the main program file.
[2696]110!------------------------------------------------------------------------------!
111 PROGRAM inifor
[3866]112
[3680]113#if defined ( __netcdf )
[2696]114
[3618]115    USE inifor_control
116    USE inifor_defs
117    USE inifor_grid,                                                           &
[3866]118        ONLY:  averaging_width_ns,                                             &
119               averaging_width_ew,                                             &
120               cfg,                                                            &   
121               cosmo_grid,                                                     &
122               f3,                                                             &
123               fini_grids,                                                     &
124               fini_io_groups,                                                 &
125               fini_variables,                                                 &
126               fini_file_lists,                                                &
127               io_group_list,                                                  &
128               lam_centre,                                                     &
129               lambda_n,                                                       &
130               nx, ny, nz,                                                     &
131               origin_lat,                                                     &
132               origin_lon,                                                     &
133               output_file,                                                    &
134               p0,                                                             &
135               phi_centre,                                                     &
136               phi_n,                                                          &
137               preprocess,                                                     &
138               palm_grid,                                                      &
139               setup_grids,                                                    &
140               setup_parameters,                                               &
141               setup_variable_tables,                                          &
142               setup_io_groups
[3618]143    USE inifor_io
144    USE inifor_transform,                                                      &
[3866]145        ONLY:  average_pressure_perturbation,                                  &
146               average_profile,                                                & 
147               geostrophic_winds,                                              &
148               get_surface_pressure,                                           &
149               interp_average_profile,                                         &
150               interpolate_1d,                                                 &
151               interpolate_1d_arr,                                             & 
152               interpolate_2d,                                                 &
153               interpolate_3d
[3618]154    USE inifor_types
[2696]155   
156    IMPLICIT NONE
157   
[4523]158    INTEGER(iwp) ::  igroup !< loop index for IO groups
159    INTEGER(iwp) ::  ivar   !< loop index for output variables
160    INTEGER(iwp) ::  iter   !< loop index for time steps
[3557]161
[3866]162    REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)     ::  output_arr !< array buffer for interpolated quantities
[4756]163    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  rho_centre_cosmo !< density profile of the centre averaging domain
[3866]164    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  ug_cosmo   !< profile of the geostrophic wind in x direction on COSMO levels
165    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  vg_cosmo   !< profile of the geostrophic wind in y direction on COSMO levels
166    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  ug_palm    !< profile of the geostrophic wind in x direction interpolated onto PALM levels
167    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  vg_palm    !< profile of the geostrophic wind in y direction interpolated onto PALM levels
[4756]168    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  rho_north_cosmo  !< density profile of the northern averaging domain
169    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  rho_south_cosmo  !< density profile of the southern averaging domain
170    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  rho_east_cosmo   !< density profile of the eastern averaging domain
171    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  rho_west_cosmo   !< density profile of the western averaging domain
172    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  p_north_cosmo    !< pressure profile of the northern averaging domain
173    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  p_south_cosmo    !< pressure profile of the southern averaging domain
174    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  p_east_cosmo     !< pressure profile of the eastern averaging domain
175    REAL(wp), ALLOCATABLE, DIMENSION(:), TARGET ::  p_west_cosmo     !< pressure profile of the western averaging domain
[3557]176
[4756]177    REAL(wp), POINTER, DIMENSION(:) ::  internal_cosmo_arr !< pointer to the currently processed internal array (density, pressure)
[3866]178    REAL(wp), POINTER, DIMENSION(:) ::  ug_vg_palm   !< pointer to the currently processed geostrophic wind component
[3557]179
180    TYPE(nc_var), POINTER        ::  output_var      !< pointer to the currently processed output variable
181    TYPE(io_group), POINTER      ::  group           !< pointer to the currently processed IO group
182    TYPE(container), ALLOCATABLE ::  input_buffer(:) !< buffer of the current IO group's input arrays
183
184    LOGICAL, SAVE ::  ug_vg_have_been_computed = .FALSE. !< flag for managing geostrophic wind allocation and computation
[3785]185    !LOGICAL, SAVE ::  debugging_output = .TRUE.          !< flag controllging output of internal variables
[2696]186   
187!> \mainpage About INIFOR
188!>  ...
189!
190!------------------------------------------------------------------------------
191!- Section 1: Initialization
192!------------------------------------------------------------------------------
[3866]193    CALL log_runtime( 'init', 'void' )
[2696]194
[3557]195!
196!-- Initialize INIFOR's parameters from command-line interface and namelists
[3866]197    CALL setup_parameters
[2696]198
[3557]199!
200!-- Initialize all grids, including interpolation neighbours and weights
[3866]201    CALL setup_grids
202    CALL log_runtime( 'time', 'init' )
[2696]203
[3557]204!
205!-- Initialize the netCDF output file and define dimensions
[3997]206    CALL setup_netcdf_dimensions( output_file, palm_grid, cfg%start_date,      &
207                                  origin_lon, origin_lat )
[3866]208    CALL log_runtime( 'time', 'write' )
[2696]209
[3557]210!
211!-- Set up the tables containing the input and output variables and set
212!-- the corresponding netCDF dimensions for each output variable
[4675]213    CALL setup_variable_tables
[4659]214    CALL setup_io_groups
215    CALL log_runtime( 'time', 'init' )
[3557]216!
217!-- Add the output variables to the netCDF output file
[4659]218    CALL setup_netcdf_variables( output_file%name, io_group_list)
219    CALL log_runtime( 'time', 'write' )
[2696]220
221!------------------------------------------------------------------------------
[3866]222!-- Section 2: Main loop
[2696]223!------------------------------------------------------------------------------
[3866]224!
225!-- Input and output variables are organized into IO groups. For instance, the
226!-- 'thermodynamics' IO group bundles the input variaebls T, P, QV and the
227!-- output variables p, theta, rho, and qv.
228!-- An IO group bunldes variables that are physically dependent on each other.
229!-- In case of the 'thermodynamics' group, theta = f(P,T), rho = f(P,T,QV).
230    DO  igroup = 1, SIZE( io_group_list )
[2696]231
232       group => io_group_list(igroup)
[3866]233       IF ( group%to_be_processed )  THEN
[2696]234         
[3866]235!--       Loop over all output time steps for the current group.
236          DO  iter = 1, group%nt 
[2696]237
238!------------------------------------------------------------------------------
[3866]239!-- Section 2.1: Read and preprocess input data
[2696]240!------------------------------------------------------------------------------
[3866]241             CALL read_input_variables( group, iter, input_buffer )
242             CALL log_runtime( 'time', 'read' )
[2696]243
[3866]244!--          Carry out all required physical conversion of the input variables
245!--          of the current IO group on the input (COSMO) grid. For instance,
246!--          horizontal velocities are rotated to the PALM coordinate system and
247!--          potential temperature is computed from the absolute temperature and
248!--          pressure.
[4659]249             CALL preprocess( group, input_buffer, cosmo_grid )
[3866]250             CALL log_runtime( 'time', 'comp' )
[2696]251
[3182]252             !TODO: move this assertion into 'preprocess'.
[3866]253             IF ( .NOT. ALL(input_buffer(:)%is_preprocessed .AND. .TRUE.) )  THEN
254                message = "Input buffers for group '" // TRIM( group%kind ) // &
255                          "' could not be preprocessed sucessfully."
256                CALL inifor_abort( 'main loop', message )
[3785]257             ENDIF
[2696]258
259!------------------------------------------------------------------------------
[3866]260!-- Section 2.2: Interpolate each output variable of the group
[2696]261!------------------------------------------------------------------------------
[3866]262             DO  ivar = 1, group%nv
[2696]263
[3866]264                output_var => group%out_vars(ivar)
[2696]265
[3866]266                IF ( output_var%to_be_processed .AND.                          &
267                     iter .LE. output_var%nt )  THEN
[2696]268
[3866]269                   message = "Processing '" // TRIM( output_var%name ) //      &
270                             "' (" // TRIM( output_var%kind ) //               &
271                             "), iteration " // TRIM( str( iter ) ) //" of " //&
272                             TRIM( str( output_var%nt ) )
273                   CALL report( 'main loop', message )
[2696]274
[3866]275                   SELECT CASE( TRIM( output_var%task ) )
[2696]276
[3866]277!--                   2D horizontal interpolation
278                      CASE( 'interpolate_2d' ) 
[2696]279                     
[3866]280                         SELECT CASE( TRIM( output_var%kind ) )
281                         
282                         CASE( 'init soil' )
283   
[4675]284                            ALLOCATE( output_arr(0:output_var%grid%nx,         &
285                                                 0:output_var%grid%ny,         &
[3866]286                                                 SIZE( output_var%grid%depths )) )
287   
288                         CASE ( 'surface forcing' )
289   
[4675]290                            ALLOCATE( output_arr(0:output_var%grid%nx,         &
[3866]291                                                 0:output_var%grid%ny, 1) )
292   
293                         CASE DEFAULT
294   
295                             message = "'" // TRIM( output_var%kind ) // "' is not a soil variable"
296                             CALL inifor_abort( "main loop", message )
297   
298                         END SELECT
299                         CALL log_runtime( 'time', 'alloc' )
300   
301                         CALL interpolate_2d( input_buffer(output_var%input_id)%array(:,:,:), &
302                                 output_arr(:,:,:), output_var%intermediate_grid, output_var )
303                         CALL log_runtime( 'time', 'comp' )
304   
305   
306!--                   Interpolation in 3D, used for atmospheric initial and
307!--                   boundary conditions.
308                      CASE ( 'interpolate_3d' )
309   
[4675]310                         ALLOCATE( output_arr(0:output_var%grid % nx,          &
311                                              0:output_var%grid % ny,          &
[3866]312                                              1:output_var%grid % nz) )
313   
314                         CALL log_runtime( 'time', 'alloc' )
[4675]315                         CALL interpolate_3d(                                  &
316                            input_buffer(output_var%input_id)%array(:,:,:),    &
317                            output_arr(:,:,:),                                 &
318                            output_var%intermediate_grid,                      &
[3866]319                            output_var%grid)
320                         CALL log_runtime( 'time', 'comp' )
321   
322!--                   Compute initial avaerage profiles (if --init-mode profile
323!--                   is used)
324                      CASE ( 'average profile' )
325   
[4675]326                         ALLOCATE( output_arr(0:0, 0:0, 1:output_var%averaging_grid%nz) )
[3866]327                         CALL log_runtime( 'time', 'alloc' )
[4675]328                         CALL interp_average_profile(                          &
329                            input_buffer(output_var%input_id)%array(:,:,:),    &
330                            output_arr(0,0,:),                                 &
[3866]331                            output_var%averaging_grid )
332   
[4675]333                         IF ( TRIM( output_var%name ) ==                       &
[3866]334                              'surface_forcing_surface_pressure' )  THEN
335   
336                            IF ( cfg%p0_is_set )  THEN
337                               output_arr(0,0,1) = p0
338                            ELSE
[4675]339                               CALL get_surface_pressure(                      &
[4756]340                                  output_arr(0,0,:),                           &
341                                  rho_centre_cosmo,                            &
[3866]342                                  output_var%averaging_grid )
343                            ENDIF
344   
[3785]345                         ENDIF
[3866]346                         CALL log_runtime( 'time', 'comp' )
[4675]347
348                      CASE ( 'average levels' )
349
350                         ALLOCATE( output_arr(0:0, 0:0, 1:output_var%averaging_grid%nz) )
351                         CALL log_runtime( 'time', 'alloc' )
352                         CALL average_profile(                                 &
353                            input_buffer(output_var%input_id)%array(:,:,:),    &
354                            output_arr(0,0,:),                                 &
355                            output_var%averaging_grid                          &
356                         )
357                         CALL log_runtime( 'time', 'comp' )
[3866]358   
359!--                   Compute internal profiles, required for differentiation of
360!--                   geostrophic wind
361                      CASE ( 'internal profile' )
362   
363                         message = "Averaging of internal profile for variable '" //&
364                            TRIM( output_var%name ) // "' is not supported."
365   
366                         SELECT CASE ( TRIM( output_var%name ) )
367   
368                         CASE( 'internal_density_centre' )
[4756]369                            ALLOCATE( rho_centre_cosmo(1:cosmo_grid%nz) )
370                            internal_cosmo_arr => rho_centre_cosmo
[3866]371   
372                         CASE( 'internal_density_north' )
[4756]373                            ALLOCATE( rho_north_cosmo(1:cosmo_grid%nz) )
374                            internal_cosmo_arr => rho_north_cosmo
[3866]375   
376                         CASE( 'internal_density_south' )
[4756]377                            ALLOCATE( rho_south_cosmo(1:cosmo_grid%nz) )
378                            internal_cosmo_arr => rho_south_cosmo
[3866]379   
380                         CASE( 'internal_density_east' )
[4756]381                            ALLOCATE( rho_east_cosmo(1:cosmo_grid%nz) )
382                            internal_cosmo_arr => rho_east_cosmo
[3866]383   
384                         CASE( 'internal_density_west' )
[4756]385                            ALLOCATE( rho_west_cosmo(1:cosmo_grid%nz) )
386                            internal_cosmo_arr => rho_west_cosmo
[3866]387   
388                         CASE( 'internal_pressure_north' )
[4756]389                            ALLOCATE( p_north_cosmo(1:cosmo_grid%nz) )
390                            internal_cosmo_arr => p_north_cosmo
[3866]391   
392                         CASE( 'internal_pressure_south' )
[4756]393                            ALLOCATE( p_south_cosmo(1:cosmo_grid%nz) )
394                            internal_cosmo_arr => p_south_cosmo
[3866]395   
396                         CASE( 'internal_pressure_east' )
[4756]397                            ALLOCATE( p_east_cosmo(1:cosmo_grid%nz) )
398                            internal_cosmo_arr => p_east_cosmo
[3866]399   
400                         CASE( 'internal_pressure_west' )
[4756]401                            ALLOCATE( p_west_cosmo(1:cosmo_grid%nz) )
402                            internal_cosmo_arr => p_west_cosmo
[3866]403   
404                         CASE DEFAULT
405                            CALL inifor_abort( 'main loop', message )
406   
407                         END SELECT
408                         CALL log_runtime( 'time', 'alloc' )
409   
410   
411                         SELECT CASE( TRIM( output_var%name ) )
412   
[4675]413                         CASE( 'internal_pressure_north',                      &
414                               'internal_pressure_south',                      &
415                               'internal_pressure_east',                       &
[3866]416                               'internal_pressure_west' )
417   
[4675]418                            CALL average_pressure_perturbation(                &
419                               input_buffer(output_var%input_id)%array(:,:,:), &
[4756]420                               internal_cosmo_arr(:),                          &
[4675]421                               cosmo_grid, output_var%averaging_grid           &
[3866]422                            )
423   
424                         CASE DEFAULT
425   
[4675]426                            CALL average_profile(                              &
427                               input_buffer(output_var%input_id)%array(:,:,:), &
[4756]428                               internal_cosmo_arr(:),                          &
[4675]429                               output_var%averaging_grid                       &
[3866]430                            )
[3395]431
432                      END SELECT
433
[3866]434                      CALL log_runtime( 'time', 'comp' )
[3395]435
[3557]436!
437!--                This case gets called twice, the first time for ug, the
438!--                second time for vg. We compute ug and vg at the first call
[3779]439!--                and keep both of them around for the second call.
[3395]440                   CASE ( 'geostrophic winds' )
441
442                      IF (.NOT. ug_vg_have_been_computed )  THEN
[3866]443                         ALLOCATE( ug_palm(output_var%grid%nz) )
444                         ALLOCATE( vg_palm(output_var%grid%nz) )
445                         ALLOCATE( ug_cosmo(cosmo_grid%nz) )
446                         ALLOCATE( vg_cosmo(cosmo_grid%nz) )
[3395]447
[3866]448                         IF ( cfg%ug_defined_by_user )  THEN
449                            ug_palm = cfg%ug
450                            vg_palm = cfg%vg
[3395]451                         ELSE
[4756]452                            CALL geostrophic_winds(                            &
453                               p_north_cosmo, p_south_cosmo, p_east_cosmo,     &
454                               p_west_cosmo, rho_centre_cosmo, f3,             &
455                               averaging_width_ew,                             &
456                               averaging_width_ns,                             &
457                               phi_n, lambda_n,                                &
458                               phi_centre, lam_centre,                         &
459                               ug_cosmo, vg_cosmo                              &
460                            )
[3779]461
[4675]462                            CALL interpolate_1d( ug_cosmo, ug_palm,            &
[3866]463                                                 output_var%grid )
[3779]464
[4675]465                            CALL interpolate_1d( vg_cosmo, vg_palm,            &
[3866]466                                                 output_var%grid )
[3785]467                         ENDIF
[3395]468
469                         ug_vg_have_been_computed = .TRUE.
470
[3785]471                      ENDIF
[3395]472
[3557]473!
[3779]474!--                   Select output array of current geostrophic wind component
[3866]475                      SELECT CASE( TRIM( output_var%name ) )
476                      CASE ( 'ls_forcing_ug' )
[3779]477                         ug_vg_palm => ug_palm
[3866]478                      CASE ( 'ls_forcing_vg' )
[3779]479                         ug_vg_palm => vg_palm
[3395]480                      END SELECT
481
[3866]482                      ALLOCATE( output_arr(1,1,output_var%grid%nz) )
[3779]483                      output_arr(1,1,:) = ug_vg_palm(:)
[3395]484
[3866]485!--                User defined constant profiles
[3182]486                   CASE ( 'set profile' )
[2696]487                     
[3866]488                      ALLOCATE( output_arr(1,1,1:nz) )
489                      CALL log_runtime( 'time', 'alloc' )
[2696]490
[3866]491                      SELECT CASE ( TRIM( output_var%name ) )
[2696]492
[3866]493                      CASE ( 'nudging_tau' )
[3182]494                          output_arr(1, 1, :) = NUDGING_TAU
495
[2696]496                      CASE DEFAULT
[3866]497                          message = "'" // TRIM( output_var%name ) //          &
498                             "' is not a valid '" // TRIM( output_var%kind ) //&
[2696]499                             "' variable kind."
[3866]500                          CALL inifor_abort( 'main loop', message )
[2696]501                      END SELECT
[3866]502                      CALL log_runtime( 'time', 'comp' )
[2696]503
504                   CASE DEFAULT
[3866]505                      message = "Processing task '" // TRIM( output_var%task ) //&
[2696]506                               "' not recognized."
[3866]507                      CALL inifor_abort( '', message )
[2696]508
509                   END SELECT
[3866]510                   CALL log_runtime( 'time', 'comp' )
[2696]511
512!------------------------------------------------------------------------------
513!- Section 2.3: Write current time step of current variable
514!------------------------------------------------------------------------------
[3779]515!
516!--                Output of geostrophic pressure profiles (with --debug
517!--                option) is currently deactivated, since they are now
518!--                defined on averaged COSMO levels instead of PALM levels
519!--                (requires definiton of COSMO levels in netCDF output.)
[3866]520                   !IF (.NOT. output_var%is_internal .OR. debugging_output)  THEN
[3779]521
[3866]522                   IF ( .NOT. output_var%is_internal )  THEN
523                      message = "Writing variable '" // TRIM( output_var%name ) // "'."
524                      CALL report( 'main loop', message )
525                      CALL update_output( output_var, output_arr, iter,        &
526                                          output_file, cfg )
527                      CALL log_runtime( 'time', 'write' )
[3785]528                   ENDIF
[2696]529
[3866]530                   IF ( ALLOCATED( output_arr ) )  DEALLOCATE( output_arr )
531                   CALL log_runtime( 'time', 'alloc' )
[2696]532
[3785]533                ENDIF
[2696]534
[3557]535!
536!--          output variable loop
[3785]537             ENDDO
[2696]538
[3401]539             ug_vg_have_been_computed = .FALSE.
[3866]540             IF ( group%kind == 'thermodynamics' )  THEN
[4756]541                DEALLOCATE( rho_centre_cosmo )
[3779]542                DEALLOCATE( ug_palm )
543                DEALLOCATE( vg_palm )
544                DEALLOCATE( ug_cosmo )
545                DEALLOCATE( vg_cosmo )
[3866]546                IF ( .NOT. cfg%ug_defined_by_user )  THEN
[4756]547                   DEALLOCATE( rho_north_cosmo )
548                   DEALLOCATE( rho_south_cosmo )
549                   DEALLOCATE( rho_east_cosmo )
550                   DEALLOCATE( rho_west_cosmo )
551                   DEALLOCATE( p_north_cosmo )
552                   DEALLOCATE( p_south_cosmo )
553                   DEALLOCATE( p_east_cosmo )
554                   DEALLOCATE( p_west_cosmo )
[3785]555                ENDIF
556             ENDIF
[3395]557
[3557]558!
559!--          Keep input buffer around for averaged (radiation) and
560!--          accumulated COSMO quantities (precipitation).
[3866]561             IF ( group%kind == 'running average' .OR. &
562                  group%kind == 'accumulated' )  THEN
[2696]563             ELSE
[3866]564                CALL report( 'main loop', 'Deallocating input buffer', cfg%debug )
565                DEALLOCATE( input_buffer )
[3785]566             ENDIF
[3866]567             CALL log_runtime( 'time', 'alloc' )
[2696]568
[3557]569!
570!--       time steps / input files loop
[3785]571          ENDDO
[2696]572
[3866]573          IF ( ALLOCATED( input_buffer ) )  THEN
574             CALL report( 'main loop', 'Deallocating input buffer', cfg%debug )
575             DEALLOCATE( input_buffer )
[3785]576          ENDIF
[3866]577          CALL log_runtime( 'time', 'alloc' )
[2696]578
579       ELSE
580
[3866]581          message = "Skipping IO group " // TRIM( str( igroup ) ) // " '" // TRIM( group%kind ) // "'"
582          IF ( ALLOCATED( group%in_var_list ) )  THEN
583              message = TRIM( message ) // " with input variable '" //         &
584              TRIM( group%in_var_list(1)%name ) // "'."
[3785]585          ENDIF
[2696]586
[3866]587          CALL report( 'main loop', message, cfg%debug )
[2696]588
[3557]589!
[3866]590!--    IO group%to_be_processed conditional
[3785]591       ENDIF
[2696]592
[3557]593!
594!-- IO groups loop
[3785]595    ENDDO
[2696]596
597!------------------------------------------------------------------------------
598!- Section 3: Clean up.
599!------------------------------------------------------------------------------
[3866]600    CALL fini_file_lists
601    CALL fini_io_groups
602    CALL fini_variables
603    !CALL fini_grids
604    CALL log_runtime( 'time', 'alloc' )
[2696]605
[4659]606    CALL report_warnings
607    CALL report_success( output_file%name )
608    CALL report_runtime
[3866]609    CALL close_log
[2696]610
[3866]611#else
[2696]612
[3866]613    USE inifor_control
614    IMPLICIT NONE
615   
616    message = "INIFOR was compiled without netCDF support, which is required for it to run. "  //     &
617              "To use INIFOR, recompile PALM with netCDF support by adding the -D__netcdf " //        &
618              "precompiler flag to your .palm.config file."
619    CALL inifor_abort( 'main loop', message )
620 
[3680]621#endif
[3866]622
[2696]623 END PROGRAM inifor
Note: See TracBrowser for help on using the repository browser.