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

Last change on this file since 2921 was 2912, checked in by knoop, 6 years ago

Added gust module interface calls to restart data modules

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