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

Last change on this file since 3182 was 3182, checked in by suehring, 6 years ago

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

  • Property svn:keywords set to Id
File size: 12.3 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!
[2718]17! Copyright 2017-2018 Leibniz Universitaet Hannover
18! Copyright 2017-2018 Deutscher Wetterdienst Offenbach
[2696]19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
[3182]23! Introduced new PALM grid stretching
24! Renamend initial-condition mode variable 'mode' to 'ic_mode'
25! Improved log messages
[2696]26!
27!
28! Former revisions:
29! -----------------
30! $Id: inifor.f90 3182 2018-07-27 13:36:03Z suehring $
31! Initial revision
32!
33!
34!
35! Authors:
36! --------
37! @author Eckhard Kadasch
38!
39! Description:
40! ------------
41!> INIFOR is an interpolation tool for generating meteorological initialization
42!> and forcing data for the urban climate model PALM-4U. The required
43!> meteorological fields are interpolated from output data of the mesoscale
44!> model COSMO-DE. This is the main program file.
45!------------------------------------------------------------------------------!
46 PROGRAM inifor
47
48    USE control
49    USE defs
50    USE grid,                                                                  &
51        ONLY:  setup_parameters, setup_grids, setup_variable_tables,           &
52               setup_io_groups, fini_grids, fini_variables, fini_io_groups,    &
[3182]53               fini_file_lists, preprocess, origin_lon, origin_lat,            &
[2696]54               output_file, io_group_list, output_var_table,                   &
[3182]55               cosmo_grid, palm_grid, nx, ny, nz, ug, vg, p0, cfg,             &
56               average_imin, average_imax, average_jmin, average_jmax
[2696]57
58    USE io
59    USE transform,                                                             &
60        ONLY:  average_profile, average_2d, interpolate_2d, interpolate_3d
61    USE types
62   
63    IMPLICIT NONE
64   
65    INTEGER                                 ::  igroup
66    INTEGER                                 ::  ivar
67    INTEGER                                 ::  iter
68    REAL(dp), ALLOCATABLE, DIMENSION(:,:,:) ::  output_arr
69    TYPE(nc_var), POINTER                   ::  output_var
70    TYPE(io_group), POINTER                 ::  group
71    TYPE(container), ALLOCATABLE            ::  input_buffer(:)
72   
73!> \mainpage About INIFOR
74!>  ...
75!
76!------------------------------------------------------------------------------
77!- Section 1: Initialization
78!------------------------------------------------------------------------------
79 CALL run_control('init', 'void')
80
81    ! Initialize INIFOR's parameters from command-line interface and namelists
82    CALL setup_parameters()
83
84    ! Initialize all grids, including interpolation neighbours and weights
85    CALL setup_grids()
86 CALL run_control('time', 'init')
87
88    ! Initialize the netCDF output file and define dimensions
[3182]89    CALL setup_netcdf_dimensions(output_file, palm_grid, cfg % start_date,    &
90                                 origin_lon, origin_lat)
[2696]91 CALL run_control('time', 'write')
92
93    ! Set up the tables containing the input and output variables and set
94    ! the corresponding netCDF dimensions for each output variable
[3182]95    CALL setup_variable_tables(cfg % ic_mode)
[2696]96 CALL run_control('time', 'write')
97
98    ! Add the output variables to the netCDF output file
99    CALL setup_netcdf_variables(output_file % name, output_var_table)
100
[3182]101    CALL setup_io_groups()
[2696]102 CALL run_control('time', 'init')
103
104!------------------------------------------------------------------------------
105!- Section 2: Main loop
106!------------------------------------------------------------------------------
107
108    DO igroup = 1, SIZE(io_group_list)
109
110       group => io_group_list(igroup)
111       IF ( group % to_be_processed )  THEN
112         
113          DO iter = 1, group % nt 
114
115!------------------------------------------------------------------------------
116!- Section 2.1: Read and preprocess input data
117!------------------------------------------------------------------------------
118             CALL read_input_variables(group, iter, input_buffer)
119 CALL run_control('time', 'read')
120
121             CALL preprocess(group, input_buffer, cosmo_grid, iter)
122 CALL run_control('time', 'comp')
123
[3182]124             !TODO: move this assertion into 'preprocess'.
[2696]125             IF ( .NOT. ALL(input_buffer(:) % is_preprocessed .AND. .TRUE.) )  THEN
126                message = "Input buffers for group '" // TRIM(group % kind) // &
127                   "' could not be preprocessed sucessfully."
128                CALL abort('main loop', message)
129             END IF
130
131!------------------------------------------------------------------------------
132!- Section 2.2: Interpolate each output variable of the group
133!------------------------------------------------------------------------------
134             DO ivar = 1, group % nv
135
136                output_var => group % out_vars( ivar )
137
138                IF ( output_var % to_be_processed .AND.                        &
139                     iter .LE. output_var % nt )  THEN
140
141                   message = "Processing '" // TRIM(output_var % name) //      &
142                             "' (" // TRIM(output_var % kind) //               &
143                             "), iteration " // TRIM(str(iter)) //" of " //    &
144                             TRIM(str(output_var % nt))
145                   CALL report('main loop', message)
146
147                   SELECT CASE( TRIM(output_var % task) )
148
149                   CASE( 'interpolate_2d' ) 
150                   
151                      SELECT CASE( TRIM(output_var % kind) )
152                       
153                      CASE( 'init soil' )
154
155                         ALLOCATE( output_arr( 0:output_var % grid % nx,       &
156                                               0:output_var % grid % ny,       &
157                                               SIZE(output_var % grid % depths) ) )
158
159                      CASE ( 'surface forcing' )
160
161                         ALLOCATE( output_arr( 0:output_var % grid % nx,       &
162                                               0:output_var % grid % ny, 1 ) )
163
164                      CASE DEFAULT
165
[3182]166                          message = "'" // TRIM(output_var % kind) // "' is not a soil variable"
167                          CALL abort("main loop", message)
[2696]168
169                      END SELECT
170 CALL run_control('time', 'alloc')
171
172                      CALL interpolate_2d(input_buffer(output_var % input_id) % array(:,:,:), &
173                              output_arr(:,:,:), output_var % intermediate_grid, output_var)
174 CALL run_control('time', 'comp')
175
176
177                   CASE ( 'interpolate_3d' )
178
179                      ALLOCATE( output_arr( 0:output_var % grid % nx,          &
180                                            0:output_var % grid % ny,          &
[3182]181                                            1:output_var % grid % nz ) )
[2696]182
183 CALL run_control('time', 'alloc')
184                      CALL interpolate_3d(                                     &
185                         input_buffer(output_var % input_id) % array(:,:,:),   &
186                         output_arr(:,:,:),                                    &
187                         output_var % intermediate_grid,                       &
188                         output_var % grid)
189 CALL run_control('time', 'comp')
190
191                   CASE ( 'average profile' )
192
193                      ALLOCATE( output_arr( 0:output_var % grid % nx,          &
194                                            0:output_var % grid % ny,          &
[3182]195                                            1:output_var % grid % nz ) )
[2696]196 CALL run_control('time', 'alloc')
197                     
198
199                      CALL average_profile(                                    &
200                         input_buffer(output_var % input_id) % array(:,:,:),   &
[3182]201                         output_arr(:,:,:), average_imin, average_imax,        &
202                         average_jmin, average_jmax,                           &
[2696]203                         output_var % intermediate_grid,                       &
204                         output_var % grid)
205 CALL run_control('time', 'comp')
206
207                   CASE ( 'average scalar' )
208
209                      ALLOCATE( output_arr(1,1,1) )
210 CALL run_control('time', 'alloc')
211                      output_arr(1,1,1) = p0
212 CALL run_control('time', 'comp')
213
[3182]214                   CASE ( 'set profile' )
[2696]215                     
[3182]216                      ALLOCATE( output_arr( 1, 1, 1:nz ) )
[2696]217 CALL run_control('time', 'alloc')
218
219                      SELECT CASE (TRIM(output_var % name))
220
221                      CASE('ls_forcing_ug')
222                          output_arr(1, 1, :) = ug
223
224                      CASE('ls_forcing_vg')
225                          output_arr(1, 1, :) = vg
226
[3182]227                      CASE('nudging_tau')
228                          output_arr(1, 1, :) = NUDGING_TAU
229
[2696]230                      CASE DEFAULT
231                          message = "'" // TRIM(output_var % name) //          &
232                             "' is not a valid '" // TRIM(output_var % kind) //&
233                             "' variable kind."
234                          CALL abort('main loop', message)
235                      END SELECT
236 CALL run_control('time', 'comp')
237
[3182]238                   CASE('average large-scale profile')
239                      message = "Averaging of large-scale forcing profiles " //&
240                                "has not been implemented, yet."
241                      CALL abort('main loop', message)
242                      !ALLOCATE( output_arr( 1, 1, 1:nz ) )
243
[2696]244                   CASE DEFAULT
245                      message = "Processing task '" // TRIM(output_var % task) //&
246                               "' not recognized."
247                      CALL abort('', message)
248
249                   END SELECT
250 CALL run_control('time', 'comp')
251
252!------------------------------------------------------------------------------
253!- Section 2.3: Write current time step of current variable
254!------------------------------------------------------------------------------
255                   message = "Writing variable '" // TRIM(output_var%name) // "'."
256                   CALL report('main loop', message)
257                   CALL update_output(output_var, output_arr, iter, output_file)
258 CALL run_control('time', 'write')
259
260                   DEALLOCATE(output_arr)
261 CALL run_control('time', 'alloc')
262
263                END IF
264
265             END DO ! ouput variables
266
267             IF ( group % kind == 'running average' .OR. &
268                  group % kind == 'accumulated' )  THEN
269                ! Keep input buffer around for averaged (radiation) and
270                ! accumulated COSMO-DE quantities (precipitation).
271             ELSE
272                CALL report('main loop', 'Deallocating input buffer')
273                DEALLOCATE(input_buffer)
274             END IF
275 CALL run_control('time', 'alloc')
276
277          END DO ! time steps / input files
278
279          IF (ALLOCATED(input_buffer))  THEN
280             CALL report('main loop', 'Deallocating input buffer')
281             DEALLOCATE(input_buffer)
282          END IF
283 CALL run_control('time', 'alloc')
284
285       ELSE
286
[3182]287          message = "Skipping IO group " // TRIM(str(igroup)) // " '" // TRIM(group % kind) // "'"
[2696]288          IF ( ALLOCATED(group % in_var_list) )  THEN
289              message = TRIM(message) // " with input variable '" //           &
290              TRIM(group % in_var_list(1) % name) // "'."
291          END IF
292
293          CALL report('main loop', message)
294
295       END IF ! IO group % to_be_processed
296
297    END DO ! IO groups
298
299!------------------------------------------------------------------------------
300!- Section 3: Clean up.
301!------------------------------------------------------------------------------
302    CALL fini_file_lists()
303    CALL fini_io_groups()
304    CALL fini_variables()
305    !CALL fini_grids()
306 CALL run_control('time', 'alloc')
307 CALL run_control('report', 'void')
308
[3182]309    message = "Finished writing dynamic driver '" // TRIM(output_file % name) // &
[2696]310              "' successfully."
311    CALL report('main loop', message)
312
313
314 END PROGRAM inifor
Note: See TracBrowser for help on using the repository browser.