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

Last change on this file since 4181 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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