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

Last change on this file since 4598 was 4535, checked in by raasch, 4 years ago

bugfix for restart data format query

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