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

Last change on this file since 3677 was 3665, checked in by raasch, 5 years ago

dummy statements added to avoid compiler warnings about unused variables, unused variables removed, ssh-call for submitting batch jobs on remote systems modified again to avoid output of login messages on specific systems

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