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

Last change on this file since 4784 was 4768, checked in by suehring, 3 years ago

Enable 3D data output also with 64-bit precision

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