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

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

restart data handling with MPI-IO added, first part

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