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

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

inifor: Support for COSMO cloud water and precipitation

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