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

Last change on this file since 3768 was 3767, checked in by raasch, 5 years ago

unused variables removed from rrd-subroutines parameter list

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