source: palm/trunk/SOURCE/gust_mod.f90 @ 3004

Last change on this file since 3004 was 3004, checked in by Giersch, 6 years ago

precipitation_rate removed, further allocation checks for data output of averaged quantities implemented, double CALL of flow_statistics at the beginning of time_integration removed, further minor bugfixes, comments added

File size: 16.4 KB
Line 
1!> @file gust_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
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 1997-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id$
27! Interfaces concerning data output updated
28!
29!
30! renamed gust_par to gust_parameters
31!
32!
33! Initial interface definition
34!
35!
36! Description:
37! ------------
38!> Gust model.
39!>
40!> @todo This is just a dummy module. The actual module ist not released yet.
41!------------------------------------------------------------------------------!
42 MODULE gust_mod
43
44    USE indices,                                                               &
45        ONLY:  nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt
46
47    USE kinds
48
49    IMPLICIT NONE
50
51    LOGICAL  ::  gust_module_enabled = .FALSE.       !< switch, if the entire module is used at all
52
53    SAVE
54
55    PRIVATE
56
57!
58!-- Public functions
59    PUBLIC &
60       gust_parin, &
61       gust_check_parameters, &
62       gust_check_data_output_pr, &
63       gust_check_data_output, &
64       gust_init_arrays, &
65       gust_init, &
66       gust_define_netcdf_grid, &
67       gust_header, &
68       gust_actions, &
69       gust_swap_timelevel, &
70       gust_3d_data_averaging, &
71       gust_data_output_2d, &
72       gust_data_output_3d, &
73       gust_statistics, &
74       gust_rrd_global, &
75       gust_wrd_global, &
76       gust_rrd_local, &
77       gust_wrd_local
78!
79!-- Public parameters, constants and initial values
80    PUBLIC &
81       gust_module_enabled
82
83
84    INTERFACE gust_parin
85       MODULE PROCEDURE gust_parin
86    END INTERFACE gust_parin
87
88    INTERFACE gust_check_parameters
89       MODULE PROCEDURE gust_check_parameters
90    END INTERFACE gust_check_parameters
91
92    INTERFACE gust_check_data_output_pr
93       MODULE PROCEDURE gust_check_data_output_pr
94    END INTERFACE gust_check_data_output_pr
95
96    INTERFACE gust_check_data_output
97       MODULE PROCEDURE gust_check_data_output
98    END INTERFACE gust_check_data_output
99
100    INTERFACE gust_init_arrays
101       MODULE PROCEDURE gust_init_arrays
102    END INTERFACE gust_init_arrays
103
104    INTERFACE gust_init
105       MODULE PROCEDURE gust_init
106    END INTERFACE gust_init
107
108    INTERFACE gust_define_netcdf_grid
109       MODULE PROCEDURE gust_define_netcdf_grid
110    END INTERFACE gust_define_netcdf_grid
111
112    INTERFACE gust_header
113       MODULE PROCEDURE gust_header
114    END INTERFACE gust_header
115
116    INTERFACE gust_actions
117       MODULE PROCEDURE gust_actions
118       MODULE PROCEDURE gust_actions_ij
119    END INTERFACE gust_actions
120
121    INTERFACE gust_swap_timelevel
122       MODULE PROCEDURE gust_swap_timelevel
123    END INTERFACE gust_swap_timelevel
124
125    INTERFACE gust_3d_data_averaging
126       MODULE PROCEDURE gust_3d_data_averaging
127    END INTERFACE gust_3d_data_averaging
128
129    INTERFACE gust_data_output_2d
130       MODULE PROCEDURE gust_data_output_2d
131    END INTERFACE gust_data_output_2d
132
133    INTERFACE gust_data_output_3d
134       MODULE PROCEDURE gust_data_output_3d
135    END INTERFACE gust_data_output_3d
136
137    INTERFACE gust_statistics
138       MODULE PROCEDURE gust_statistics
139    END INTERFACE gust_statistics
140
141    INTERFACE gust_rrd_global
142       MODULE PROCEDURE gust_rrd_global
143    END INTERFACE gust_rrd_global
144
145    INTERFACE gust_wrd_global
146       MODULE PROCEDURE gust_wrd_global
147    END INTERFACE gust_wrd_global
148
149    INTERFACE gust_rrd_local
150       MODULE PROCEDURE gust_rrd_local
151    END INTERFACE gust_rrd_local
152
153    INTERFACE gust_wrd_local
154       MODULE PROCEDURE gust_wrd_local
155    END INTERFACE gust_wrd_local
156
157 CONTAINS
158
159
160!------------------------------------------------------------------------------!
161! Description:
162! ------------
163!> Parin for &gust_parameters for gust module
164!------------------------------------------------------------------------------!
165    SUBROUTINE gust_parin
166
167
168       IMPLICIT NONE
169
170       CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
171
172       NAMELIST /gust_parameters/  &
173          gust_module_enabled
174
175       line = ' '
176!
177!--    Try to find gust module package
178       REWIND ( 11 )
179       line = ' '
180       DO   WHILE ( INDEX( line, '&gust_parameters' ) == 0 )
181          READ ( 11, '(A)', END=10 )  line
182       ENDDO
183       BACKSPACE ( 11 )
184!
185!--    Read user-defined namelist
186       READ ( 11, gust_parameters )
187!
188!--    Set flag that indicates that the gust module is switched on
189       gust_module_enabled = .TRUE.
190
19110     CONTINUE
192
193
194    END SUBROUTINE gust_parin
195
196
197!------------------------------------------------------------------------------!
198! Description:
199! ------------
200!> Check parameters routine for gust module
201!------------------------------------------------------------------------------!
202    SUBROUTINE gust_check_parameters
203
204
205       IMPLICIT NONE
206
207
208    END SUBROUTINE gust_check_parameters
209
210
211!------------------------------------------------------------------------------!
212! Description:
213! ------------
214!> Check data output of profiles for gust module
215!------------------------------------------------------------------------------!
216    SUBROUTINE gust_check_data_output_pr( variable, var_count, unit, dopr_unit )
217
218
219       IMPLICIT NONE
220
221       CHARACTER (LEN=*) ::  unit      !<
222       CHARACTER (LEN=*) ::  variable  !<
223       CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
224
225       INTEGER(iwp) ::  var_count      !<
226
227
228    END SUBROUTINE gust_check_data_output_pr
229
230!------------------------------------------------------------------------------!
231! Description:
232! ------------
233!> Check data output for gust module
234!------------------------------------------------------------------------------!
235    SUBROUTINE gust_check_data_output( var, unit )
236
237
238       IMPLICIT NONE
239
240       CHARACTER (LEN=*) ::  unit  !<
241       CHARACTER (LEN=*) ::  var   !<
242
243
244    END SUBROUTINE gust_check_data_output
245
246
247!------------------------------------------------------------------------------!
248! Description:
249! ------------
250!> Allocate gust module arrays and define pointers
251!------------------------------------------------------------------------------!
252    SUBROUTINE gust_init_arrays
253
254
255       IMPLICIT NONE
256
257
258    END SUBROUTINE gust_init_arrays
259
260
261!------------------------------------------------------------------------------!
262! Description:
263! ------------
264!> Initialization of the gust module
265!------------------------------------------------------------------------------!
266    SUBROUTINE gust_init( dots_label, dots_unit, dots_num, dots_max )
267
268
269       IMPLICIT NONE
270
271       INTEGER(iwp) ::  dots_num
272       INTEGER(iwp) ::  dots_max
273       CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_unit
274       CHARACTER (LEN=13), DIMENSION(dots_max) :: dots_label
275
276
277    END SUBROUTINE gust_init
278
279
280!------------------------------------------------------------------------------!
281!
282! Description:
283! ------------
284!> Subroutine defining appropriate grid for netcdf variables.
285!> It is called out from subroutine netcdf.
286!------------------------------------------------------------------------------!
287    SUBROUTINE gust_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
288
289
290       IMPLICIT NONE
291
292       CHARACTER (LEN=*), INTENT(IN)  ::  var         !<
293       LOGICAL, INTENT(IN)           ::  found       !<
294       CHARACTER (LEN=*), INTENT(IN) ::  grid_x      !<
295       CHARACTER (LEN=*), INTENT(IN) ::  grid_y      !<
296       CHARACTER (LEN=*), INTENT(IN) ::  grid_z      !<
297
298
299    END SUBROUTINE gust_define_netcdf_grid
300
301
302!------------------------------------------------------------------------------!
303! Description:
304! ------------
305!> Header output for gust module
306!------------------------------------------------------------------------------!
307    SUBROUTINE gust_header ( io )
308
309
310       IMPLICIT NONE
311
312       INTEGER(iwp), INTENT(IN) ::  io  !< Unit of the output file
313
314
315    END SUBROUTINE gust_header
316
317
318!------------------------------------------------------------------------------!
319! Description:
320! ------------
321!> Call for all grid points
322!------------------------------------------------------------------------------!
323    SUBROUTINE gust_actions( location )
324
325
326       IMPLICIT NONE
327
328       CHARACTER (LEN=*) ::  location !<
329
330
331    END SUBROUTINE gust_actions
332
333
334!------------------------------------------------------------------------------!
335! Description:
336! ------------
337!> Call for grid point i,j
338!------------------------------------------------------------------------------!
339    SUBROUTINE gust_actions_ij( i, j, location )
340
341
342       IMPLICIT NONE
343
344       CHARACTER (LEN=*) ::  location
345
346       INTEGER(iwp) ::  i
347       INTEGER(iwp) ::  j
348
349
350    END SUBROUTINE gust_actions_ij
351
352
353!------------------------------------------------------------------------------!
354! Description:
355! ------------
356!> Swapping of timelevels
357!------------------------------------------------------------------------------!
358    SUBROUTINE gust_swap_timelevel ( mod_count )
359
360
361       IMPLICIT NONE
362
363       INTEGER, INTENT(IN) :: mod_count
364
365
366    END SUBROUTINE gust_swap_timelevel
367
368
369!------------------------------------------------------------------------------!
370!
371! Description:
372! ------------
373!> Subroutine for averaging 3D data
374!------------------------------------------------------------------------------!
375    SUBROUTINE gust_3d_data_averaging( mode, variable )
376
377
378       IMPLICIT NONE
379
380       CHARACTER (LEN=*) ::  mode    !<
381       CHARACTER (LEN=*) :: variable !<
382
383
384    END SUBROUTINE gust_3d_data_averaging
385
386!------------------------------------------------------------------------------!
387!
388! Description:
389! ------------
390!> Subroutine defining 2D output variables
391!------------------------------------------------------------------------------!
392    SUBROUTINE gust_data_output_2d( av, variable, found, grid, local_pf,       &
393                                    two_d, nzb_do, nzt_do )
394
395
396       IMPLICIT NONE
397
398       CHARACTER (LEN=*) ::  grid     !<
399       CHARACTER (LEN=*) ::  variable !<
400
401       INTEGER(iwp) ::  av     !< flag to control data output of instantaneous or time-averaged data
402       INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
403       INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
404
405       LOGICAL      ::  found !<
406       LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
407
408       REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
409
410       REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
411
412
413    END SUBROUTINE gust_data_output_2d
414
415
416!------------------------------------------------------------------------------!
417!
418! Description:
419! ------------
420!> Subroutine defining 3D output variables
421!------------------------------------------------------------------------------!
422    SUBROUTINE gust_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
423
424
425       IMPLICIT NONE
426
427       CHARACTER (LEN=*) ::  variable !<
428
429       INTEGER(iwp) ::  av    !<
430       INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
431       INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
432
433       LOGICAL      ::  found !<
434
435       REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
436
437       REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
438
439
440    END SUBROUTINE gust_data_output_3d
441
442
443!------------------------------------------------------------------------------!
444! Description:
445! ------------
446!> This routine computes profile and timeseries data for the gust module.
447!------------------------------------------------------------------------------!
448    SUBROUTINE gust_statistics( mode, sr, tn, dots_max )
449
450
451       IMPLICIT NONE
452
453       CHARACTER (LEN=*) ::  mode   !<
454
455       INTEGER(iwp) ::  sr   !<
456       INTEGER(iwp) ::  tn   !<
457       INTEGER(iwp) ::  dots_max   !<
458
459
460    END SUBROUTINE gust_statistics
461
462
463!------------------------------------------------------------------------------!
464! Description:
465! ------------
466!> This routine reads the respective restart data for the gust module.
467!------------------------------------------------------------------------------!
468    SUBROUTINE gust_rrd_global( found )
469
470
471       USE control_parameters,                                                 &
472           ONLY: length, restart_string
473
474
475       IMPLICIT NONE
476
477       LOGICAL, INTENT(OUT)  ::  found
478
479
480       found = .TRUE.
481
482
483       SELECT CASE ( restart_string(1:length) )
484
485          CASE ( 'global_paramter' )
486!             READ ( 13 )  global_parameter
487
488          CASE DEFAULT
489
490             found = .FALSE.
491
492       END SELECT
493
494
495    END SUBROUTINE gust_rrd_global
496
497
498!------------------------------------------------------------------------------!
499! Description:
500! ------------
501!> This routine reads the respective restart data for the gust module.
502!------------------------------------------------------------------------------!
503    SUBROUTINE gust_rrd_local( i, k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,      &
504                               nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
505                               nysc, nys_on_file, tmp_2d, tmp_3d, found )
506
507
508       USE control_parameters
509
510       USE indices
511
512       USE kinds
513
514       USE pegrid
515
516
517       IMPLICIT NONE
518
519       INTEGER(iwp) ::  i               !<
520       INTEGER(iwp) ::  k               !<
521       INTEGER(iwp) ::  nxlc            !<
522       INTEGER(iwp) ::  nxlf            !<
523       INTEGER(iwp) ::  nxl_on_file     !<
524       INTEGER(iwp) ::  nxrc            !<
525       INTEGER(iwp) ::  nxrf            !<
526       INTEGER(iwp) ::  nxr_on_file     !<
527       INTEGER(iwp) ::  nync            !<
528       INTEGER(iwp) ::  nynf            !<
529       INTEGER(iwp) ::  nyn_on_file     !<
530       INTEGER(iwp) ::  nysc            !<
531       INTEGER(iwp) ::  nysf            !<
532       INTEGER(iwp) ::  nys_on_file     !<
533
534       LOGICAL, INTENT(OUT)  ::  found
535
536       REAL(wp), DIMENSION(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_2d   !<
537       REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
538
539!
540!-- Here the reading of user-defined restart data follows:
541!-- Sample for user-defined output
542
543
544       found = .TRUE.
545
546
547       SELECT CASE ( restart_string(1:length) )
548
549          CASE ( 'u2_av' )
550!             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
551!                  ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
552!             ENDIF
553!             IF ( k == 1 )  READ ( 13 )  tmp_3d
554!                u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
555!                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
556!
557          CASE DEFAULT
558
559             found = .FALSE.
560
561          END SELECT
562
563
564    END SUBROUTINE gust_rrd_local
565
566
567!------------------------------------------------------------------------------!
568! Description:
569! ------------
570!> This routine writes the respective restart data for the gust module.
571!------------------------------------------------------------------------------!
572    SUBROUTINE gust_wrd_global
573
574
575       IMPLICIT NONE
576
577! needs preceeding allocation if array
578!       CALL wrd_write_string( 'global_parameter' )
579!       WRITE ( 14 )  global_parameter
580
581!       IF ( ALLOCATED( inflow_damping_factor ) )  THEN
582!          CALL wrd_write_string( 'inflow_damping_factor' )
583!          WRITE ( 14 )  inflow_damping_factor
584!       ENDIF
585
586
587    END SUBROUTINE gust_wrd_global
588
589
590!------------------------------------------------------------------------------!
591! Description:
592! ------------
593!> This routine writes the respective restart data for the gust module.
594!------------------------------------------------------------------------------!
595    SUBROUTINE gust_wrd_local
596
597
598       IMPLICIT NONE
599
600
601! needs preceeding allocation because sould be array
602!          IF ( ALLOCATED( u2_av ) )  THEN
603!             CALL wrd_write_string( 'u2_av' )
604!             WRITE ( 14 )  u2_av
605!          ENDIF
606
607
608    END SUBROUTINE gust_wrd_local
609
610
611
612 END MODULE gust_mod
Note: See TracBrowser for help on using the repository browser.