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

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

added restart with MPI-IO for reading local arrays

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