source: palm/trunk/TUTORIALS/cases/lsm_short/USER_CODE/user_module.f90

Last change on this file was 4843, checked in by raasch, 3 years ago

local namelist parameter added to switch off the module although the respective module namelist appears in the namelist file, further copyright updates

File size: 45.2 KB
Line 
1!> @file user_module.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
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.
8!
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.
12!
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/>.
15!
16! Copyright 1997-2021 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: user_module.f90 4535 2020-05-15 12:07:23Z raasch $
27! bugfix for restart data format query
28!
29! 4517 2020-05-03 14:29:30Z raasch
30! added restart with MPI-IO for reading local arrays
31!
32! 4504 2020-04-20 12:11:24Z raasch
33! hint for setting rmask arrays added
34!
35! 4497 2020-04-15 10:20:51Z raasch
36! file re-formatted to follow the PALM coding standard
37!
38! 4495 2020-04-13 20:11:20Z raasch
39! restart data handling with MPI-IO added
40!
41! 4360 2020-01-07 11:25:50Z suehring
42! Introduction of wall_flags_total_0, which currently sets bits based on static topography
43! information used in wall_flags_static_0
44!
45! 4329 2019-12-10 15:46:36Z motisi
46! Renamed wall_flags_0 to wall_flags_static_0
47!
48! 4287 2019-11-01 14:50:20Z raasch
49! reading of namelist file and actions in case of namelist errors revised so that statement labels
50! and goto statements are not required any more; this revision also removes a previous bug which
51! appeared when the namelist has been commented out in the namelist file
52!
53! 4182 2019-08-22 15:20:23Z scharf
54! Corrected "Former revisions" section
55!
56! 3986 2019-05-20 14:08:14Z Giersch
57! Redundant integration of control parameters in user_rrd_global removed
58!
59! 3911 2019-04-17 12:26:19Z knoop
60! Bugfix: added before_prognostic_equations case in user_actions
61!
62! 3768 2019-02-27 14:35:58Z raasch
63! variables commented + statements added to avoid compiler warnings about unused variables
64!
65! 3767 2019-02-27 08:18:02Z raasch
66! unused variable for file index removed from rrd-subroutines parameter list
67!
68! 3747 2019-02-16 15:15:23Z gronemeier
69! Add routine user_init_arrays
70!
71! 3703 2019-01-29 16:43:53Z knoop
72! An example for a user defined global variable has been added (Giersch)
73!
74! Revision 1.1  1998/03/24 15:29:04  raasch
75! Initial revision
76!
77!
78! Description:
79! ------------
80!> Declaration of user-defined variables. This module may only be used in the user-defined routines
81!> (contained in user_interface.f90).
82!--------------------------------------------------------------------------------------------------!
83 MODULE user
84
85    USE arrays_3d
86
87    USE control_parameters
88
89    USE cpulog
90
91    USE indices
92
93    USE kinds
94
95    USE pegrid
96
97    USE statistics
98
99    USE surface_mod
100
101    IMPLICIT NONE
102
103    INTEGER(iwp) ::  dots_num_palm      !<
104    INTEGER(iwp) ::  dots_num_user = 0  !<
105    INTEGER(iwp) ::  user_idummy        !<
106
107    LOGICAL ::  user_module_enabled = .FALSE.  !<
108
109    REAL(wp) ::  user_rdummy  !<
110
111!
112!-- Sample for user-defined output
113!    REAL(wp) :: global_parameter  !< user defined global parameter
114!
115!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2      !< user defined array
116!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2_av   !< user defined array
117!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ustvst  !< user defined array
118     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_h, v_h_av       !< user defined array
119
120    SAVE
121
122    PRIVATE
123
124!
125!- Public functions
126    PUBLIC                                                                                         &
127       user_actions,                                                                               &
128       user_check_data_output,                                                                     &
129       user_check_data_output_pr,                                                                  &
130       user_check_data_output_ts,                                                                  &
131       user_check_parameters,                                                                      &
132       user_data_output_2d,                                                                        &
133       user_data_output_3d,                                                                        &
134       user_define_netcdf_grid,                                                                    &
135       user_header,                                                                                &
136       user_init,                                                                                  &
137       user_init_arrays,                                                                           &
138       user_last_actions,                                                                          &
139       user_parin,                                                                                 &
140       user_rrd_global,                                                                            &
141       user_rrd_local,                                                                             &
142       user_statistics,                                                                            &
143       user_3d_data_averaging,                                                                     &
144       user_wrd_global,                                                                            &
145       user_wrd_local
146
147
148!
149!- Public parameters, constants and initial values
150   PUBLIC                                                                                          &
151      user_module_enabled
152
153    INTERFACE user_parin
154       MODULE PROCEDURE user_parin
155    END INTERFACE user_parin
156
157    INTERFACE user_check_parameters
158       MODULE PROCEDURE user_check_parameters
159    END INTERFACE user_check_parameters
160
161    INTERFACE user_check_data_output_ts
162       MODULE PROCEDURE user_check_data_output_ts
163    END INTERFACE user_check_data_output_ts
164
165    INTERFACE user_check_data_output_pr
166       MODULE PROCEDURE user_check_data_output_pr
167    END INTERFACE user_check_data_output_pr
168
169    INTERFACE user_check_data_output
170       MODULE PROCEDURE user_check_data_output
171    END INTERFACE user_check_data_output
172
173    INTERFACE user_define_netcdf_grid
174       MODULE PROCEDURE user_define_netcdf_grid
175    END INTERFACE user_define_netcdf_grid
176
177    INTERFACE user_init
178       MODULE PROCEDURE user_init
179    END INTERFACE user_init
180
181    INTERFACE user_init_arrays
182       MODULE PROCEDURE user_init_arrays
183    END INTERFACE user_init_arrays
184
185    INTERFACE user_header
186       MODULE PROCEDURE user_header
187    END INTERFACE user_header
188
189    INTERFACE user_actions
190       MODULE PROCEDURE user_actions
191       MODULE PROCEDURE user_actions_ij
192    END INTERFACE user_actions
193
194    INTERFACE user_3d_data_averaging
195       MODULE PROCEDURE user_3d_data_averaging
196    END INTERFACE user_3d_data_averaging
197
198    INTERFACE user_data_output_2d
199       MODULE PROCEDURE user_data_output_2d
200    END INTERFACE user_data_output_2d
201
202    INTERFACE user_data_output_3d
203       MODULE PROCEDURE user_data_output_3d
204    END INTERFACE user_data_output_3d
205
206    INTERFACE user_statistics
207       MODULE PROCEDURE user_statistics
208    END INTERFACE user_statistics
209
210    INTERFACE user_rrd_global
211       MODULE PROCEDURE user_rrd_global_ftn
212       MODULE PROCEDURE user_rrd_global_mpi
213    END INTERFACE user_rrd_global
214
215    INTERFACE user_rrd_local
216       MODULE PROCEDURE user_rrd_local_ftn
217       MODULE PROCEDURE user_rrd_local_mpi
218    END INTERFACE user_rrd_local
219
220    INTERFACE user_wrd_global
221       MODULE PROCEDURE user_wrd_global
222    END INTERFACE user_wrd_global
223
224    INTERFACE user_wrd_local
225       MODULE PROCEDURE user_wrd_local
226    END INTERFACE user_wrd_local
227
228    INTERFACE user_last_actions
229       MODULE PROCEDURE user_last_actions
230    END INTERFACE user_last_actions
231
232
233 CONTAINS
234
235
236!--------------------------------------------------------------------------------------------------!
237! Description:
238! ------------
239!> Parin for &user_parameters for user module
240!--------------------------------------------------------------------------------------------------!
241 SUBROUTINE user_parin
242
243    CHARACTER (LEN=80) ::  line  !< string containing the last line read from namelist file
244
245    INTEGER(iwp) ::  i          !<
246    INTEGER(iwp) ::  io_status  !< status after reading the namelist file
247    INTEGER(iwp) ::  j          !<
248
249
250    NAMELIST /user_parameters/                                                                     &
251       data_output_masks_user,                                                                     &
252       data_output_pr_user,                                                                        &
253       data_output_user,                                                                           &
254       region
255
256!
257!-- Next statement is to avoid compiler warnings about unused variables. Please remove in case
258!-- that you are using them.
259    IF ( dots_num_palm == 0  .OR.  dots_num_user == 0  .OR.  user_idummy == 0  .OR.                &
260         user_rdummy == 0.0_wp )  CONTINUE
261
262!
263!-- Set revision number of this default interface version. It will be checked within the main
264!-- program (palm). Please change the revision number in case that the current revision does not
265!-- match with previous revisions (e.g. if routines have been added/deleted or if parameter lists
266!-- in subroutines have been changed).
267    user_interface_current_revision = 'r4495'
268
269!
270!-- Position the namelist-file at the beginning (it has already been opened in parin), and try to
271!-- read (find) a namelist named "user_parameters".
272    REWIND ( 11 )
273    READ( 11, user_parameters, IOSTAT=io_status )
274
275!
276!-- Actions depending on the READ status
277    IF ( io_status == 0 )  THEN
278!
279!--    User namelist found and correctly read. Set default module switch to true. This activates
280!--    calls of the user-interface subroutines.
281       user_module_enabled = .TRUE.
282
283    ELSEIF ( io_status > 0 )  THEN
284!
285!--    User namelist was found, but contained errors. Print an error message containing the line
286!--    that caused the problem
287       BACKSPACE( 11 )
288       READ( 11 , '(A)') line
289       CALL parin_fail_message( 'user_parameters', line )
290
291    ENDIF
292
293!
294!-- Determine the number of user-defined profiles and append them to the standard data output
295!-- (data_output_pr)
296    IF ( user_module_enabled )  THEN
297       IF ( data_output_pr_user(1) /= ' ' )  THEN
298          i = 1
299          DO WHILE ( data_output_pr(i) /= ' '  .AND.  i <= 100 )
300             i = i + 1
301          ENDDO
302          j = 1
303          DO WHILE ( data_output_pr_user(j) /= ' '  .AND.  j <= 100 )
304             data_output_pr(i) = data_output_pr_user(j)
305             max_pr_user_tmp   = max_pr_user_tmp + 1
306             i = i + 1
307             j = j + 1
308          ENDDO
309       ENDIF
310    ENDIF
311
312
313 END SUBROUTINE user_parin
314
315
316!--------------------------------------------------------------------------------------------------!
317! Description:
318! ------------
319!> Check &userpar control parameters and deduce further quantities.
320!--------------------------------------------------------------------------------------------------!
321 SUBROUTINE user_check_parameters
322
323!
324!-- Here the user may add code to check the validity of further &userpar control parameters or
325!-- deduce further quantities.
326
327
328 END SUBROUTINE user_check_parameters
329
330
331!--------------------------------------------------------------------------------------------------!
332! Description:
333! ------------
334!> Set module-specific timeseries units and labels
335!--------------------------------------------------------------------------------------------------!
336 SUBROUTINE user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
337
338    INTEGER(iwp),      INTENT(IN)     ::  dots_max  !<
339    INTEGER(iwp),      INTENT(INOUT)  ::  dots_num  !<
340
341    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_label  !<
342    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_unit   !<
343
344!
345!-- Next line is to avoid compiler warning about unused variables. Please remove.
346    IF ( dots_num == 0  .OR.  dots_label(1)(1:1) == ' '  .OR.  dots_unit(1)(1:1) == ' ' )  CONTINUE
347
348!
349!-- Sample for user-defined time series:
350!-- For each time series quantity you have to give a label and a unit, which will be used for the
351!-- NetCDF file. They must not contain more than seven characters. The value of dots_num has to be
352!-- increased by the number of new time series quantities. Its old value has to be stored in
353!-- dots_num_palm. See routine user_statistics on how to calculate and output these quantities.
354
355!    dots_num_palm = dots_num
356
357!    dots_num = dots_num + 1
358!    dots_num_user = dots_num_user + 1
359!    dots_label(dots_num) = 'abs_umx'
360!    dots_unit(dots_num)  = 'm/s'
361
362!    dots_num = dots_num + 1
363!    dots_num_user = dots_num_user + 1
364!    dots_label(dots_num) = 'abs_vmx'
365!    dots_unit(dots_num)  = 'm/s'
366
367
368 END SUBROUTINE user_check_data_output_ts
369
370
371!--------------------------------------------------------------------------------------------------!
372! Description:
373! ------------
374!> Set the unit of user defined profile output quantities. For those variables not recognized by the
375!> user, the parameter unit is set to "illegal", which tells the calling routine that the
376!> output variable is not defined and leads to a program abort.
377!--------------------------------------------------------------------------------------------------!
378 SUBROUTINE user_check_data_output_pr( variable, var_count, unit, dopr_unit )
379
380
381    USE profil_parameter
382
383
384    CHARACTER (LEN=*) ::  unit      !<
385    CHARACTER (LEN=*) ::  variable  !<
386    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
387
388!    INTEGER(iwp) ::  user_pr_index  !<
389    INTEGER(iwp) ::  var_count      !<
390
391!
392!-- Next line is to avoid compiler warning about unused variables. Please remove.
393    IF ( unit(1:1) == ' '  .OR.  dopr_unit(1:1) == ' '  .OR.  var_count == 0 )  CONTINUE
394
395    SELECT CASE ( TRIM( variable ) )
396
397!
398!--    Uncomment and extend the following lines, if necessary.
399!--    Add additional CASE statements depending on the number of quantities for which profiles are
400!--    to be calculated. The respective calculations to be performed have to be added in routine
401!--    user_statistics. The quantities are (internally) identified by a user-profile-number
402!--    (see variable "user_pr_index" below). The first user-profile must be assigned the number
403!--    "pr_palm+1", the second one "pr_palm+2", etc. The respective user-profile-numbers have also
404!--    to be used in routine user_statistics!
405!       CASE ( 'u*v*' )                      ! quantity string as given in data_output_pr_user
406!          user_pr_index = pr_palm + 1
407!          dopr_index(var_count)  = user_pr_index    ! quantities' user-profile-number
408!          dopr_unit = 'm2/s2'  ! quantity unit
409!          unit = dopr_unit
410!          hom(:,2,user_pr_index,:) = SPREAD( zu, 2, statistic_regions+1 )
411!                                            ! grid on which the quantity is defined (use zu or zw)
412!
413
414       CASE DEFAULT
415          unit = 'illegal'
416
417    END SELECT
418
419
420 END SUBROUTINE user_check_data_output_pr
421
422
423!--------------------------------------------------------------------------------------------------!
424! Description:
425! ------------
426!> Set the unit of user defined output quantities. For those variables not recognized by the user,
427!> the parameter unit is set to "illegal", which tells the calling routine that the output variable
428!> is not defined and leads to a program abort.
429!--------------------------------------------------------------------------------------------------!
430 SUBROUTINE user_check_data_output( variable, unit )
431
432
433    CHARACTER (LEN=*) ::  unit      !<
434    CHARACTER (LEN=*) ::  variable  !<
435
436
437    SELECT CASE ( TRIM( variable ) )
438
439!
440!--    Uncomment and extend the following lines, if necessary
441!       CASE ( 'u2' )
442!          unit = 'm2/s2'
443!
444!       CASE ( 'u*v*' )
445!          unit = 'm2/s2'
446!
447      CASE ( 'v_h' )
448         unit = 'm/s'
449
450       CASE DEFAULT
451          unit = 'illegal'
452
453    END SELECT
454
455
456 END SUBROUTINE user_check_data_output
457
458
459!--------------------------------------------------------------------------------------------------!
460! Description:
461! ------------
462!> Initialize user-defined arrays
463!--------------------------------------------------------------------------------------------------!
464 SUBROUTINE user_init_arrays
465
466
467!    INTEGER(iwp) :: i       !< loop index
468!    INTEGER(iwp) :: j       !< loop index
469!    INTEGER(iwp) :: region  !< index for loop over statistic regions
470
471!
472!-- Allocate user-defined arrays and set flags for statistic regions.
473!-- Sample for user-defined output
474!    ALLOCATE( u2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
475!    ALLOCATE( ustvst(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
476    ALLOCATE( v_h(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
477
478
479!
480!-- Example for defining a statistic region:
481!-- ATTENTION: rmask = 0 is required at the ghost boundaries to guarantee correct statistic
482!--            evaluations (otherwise ghost points would be counted twice). This setting has
483!--            already been cared for in routine init_3d_model. Please don't set the ghost points
484!--            /= 0. i.e. run the following loop only over nxl,nxr and nys,nyn.
485!     IF ( statistic_regions >= 1 )  THEN
486!        region = 1
487!
488!        rmask(:,:,region) = 0.0_wp
489!        DO  i = nxl, nxr
490!           IF ( i >= INT( 0.25 * nx ) .AND. i <= INT( 0.75 * nx ) )  THEN
491!              DO  j = nys, nyn
492!                 IF ( i >= INT( 0.25 * ny ) .AND. i <= INT( 0.75 * ny ) )  THEN
493!                    rmask(j,i,region) = 1.0_wp
494!                 ENDIF
495!              ENDDO
496!           ENDIF
497!        ENDDO
498!
499!     ENDIF
500
501 END SUBROUTINE user_init_arrays
502
503
504!--------------------------------------------------------------------------------------------------!
505! Description:
506! ------------
507!> Execution of user-defined initializing actions
508!--------------------------------------------------------------------------------------------------!
509 SUBROUTINE user_init
510
511
512!    CHARACTER(LEN=20) :: field_char  !<
513!
514!-- Here the user-defined initializing actions follow:
515!-- Sample for user-defined output
516!    ustvst = 0.0_wp
517    v_h = 0.0_wp
518
519
520 END SUBROUTINE user_init
521
522
523!--------------------------------------------------------------------------------------------------!
524! Description:
525! ------------
526!> Set the grids on which user-defined output quantities are defined. Allowed values for grid_x are
527!> "x" and "xu", for grid_y "y" and "yv", and for grid_z "zu" and "zw".
528!--------------------------------------------------------------------------------------------------!
529 SUBROUTINE user_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
530
531
532    CHARACTER (LEN=*) ::  grid_x     !<
533    CHARACTER (LEN=*) ::  grid_y     !<
534    CHARACTER (LEN=*) ::  grid_z     !<
535    CHARACTER (LEN=*) ::  variable   !<
536
537    LOGICAL ::  found   !<
538
539
540    SELECT CASE ( TRIM( variable ) )
541
542!
543!--    Uncomment and extend the following lines, if necessary
544!       CASE ( 'u2', 'u2_xy', 'u2_xz', 'u2_yz' )
545!          found  = .TRUE.
546!          grid_x = 'xu'
547!          grid_y = 'y'
548!          grid_z = 'zu'
549
550!       CASE ( 'u*v*', 'u*v*_xy', 'u*v*_xz', 'u*v*_yz' )
551!          found  = .TRUE.
552!          grid_x = 'x'
553!          grid_y = 'y'
554!          grid_z = 'zu'
555
556      CASE ( 'v_h', 'v_h_av' )
557         found  = .TRUE.
558         grid_x = 'xu'
559         grid_y = 'y'
560         grid_z = 'zu'
561
562       CASE DEFAULT
563          found  = .FALSE.
564          grid_x = 'none'
565          grid_y = 'none'
566          grid_z = 'none'
567
568    END SELECT
569
570
571 END SUBROUTINE user_define_netcdf_grid
572
573
574
575
576!--------------------------------------------------------------------------------------------------!
577! Description:
578! ------------
579!> Print a header with user-defined information.
580!--------------------------------------------------------------------------------------------------!
581 SUBROUTINE user_header( io )
582
583
584    INTEGER(iwp) ::  i   !<
585    INTEGER(iwp) ::  io  !<
586
587!
588!-- If no user-defined variables are read from the namelist-file, no information will be printed.
589    IF ( .NOT. user_module_enabled )  THEN
590       WRITE ( io, 100 )
591       RETURN
592    ENDIF
593
594!
595!-- Printing the information.
596    WRITE ( io, 110 )
597
598    IF ( statistic_regions /= 0 )  THEN
599       WRITE ( io, 200 )
600       DO  i = 0, statistic_regions
601          WRITE ( io, 201 )  i, region(i)
602       ENDDO
603    ENDIF
604
605!
606!-- Format-descriptors
607100 FORMAT (//' *** no user-defined variables found'/)
608110 FORMAT (//1X,78('#') // ' User-defined variables and actions:' /                               &
609            ' -----------------------------------'//)
610200 FORMAT (' Output of profiles and time series for following regions:' /)
611201 FORMAT (4X,'Region ',I1,':   ',A)
612
613
614 END SUBROUTINE user_header
615
616
617!--------------------------------------------------------------------------------------------------!
618! Description:
619! ------------
620!> Call for all grid points
621!--------------------------------------------------------------------------------------------------!
622 SUBROUTINE user_actions( location )
623
624
625    CHARACTER(LEN=*) ::  location  !<
626
627    INTEGER(iwp) ::  i  !<
628    INTEGER(iwp) ::  j  !<
629    INTEGER(iwp) ::  k  !<
630
631    CALL cpu_log( log_point(24), 'user_actions', 'start' )
632
633!
634!-- Here the user-defined actions follow. No calls for single grid points are allowed at locations
635!-- before and after the timestep, since these calls are not within an i,j-loop
636    SELECT CASE ( location )
637
638       CASE ( 'before_timestep' )
639!
640!--       Enter actions to be done before every timestep here
641
642       CASE ( 'before_prognostic_equations' )
643!
644!--       Enter actions to be done before all prognostic equations here
645
646       CASE ( 'after_integration' )
647!
648!--       Enter actions to be done after every time integration (before data output)
649!--       Sample for user-defined output:
650!          DO  i = nxlg, nxrg
651!             DO  j = nysg, nyng
652!                DO  k = nzb, nzt
653!                   u2(k,j,i) = u(k,j,i)**2
654!                ENDDO
655!             ENDDO
656!          ENDDO
657!          DO  i = nxlg, nxr
658!             DO  j = nysg, nyn
659!                DO  k = nzb, nzt+1
660!                   ustvst(k,j,i) =  &
661!                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) *                      &
662!                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
663!                ENDDO
664!             ENDDO
665!          ENDDO
666
667          DO  i = nxlg, nxrg
668             DO  j = nysg, nyng
669                DO  k = nzb, nzt
670                   v_h(k,j,i) = SQRT( u(k,j,i)**2.0_wp + v(k,j,i)**2.0_wp )
671                ENDDO
672             ENDDO
673          ENDDO
674
675       CASE ( 'after_timestep' )
676!
677!--       Enter actions to be done after every timestep here
678
679
680       CASE ( 'u-tendency' )
681!
682!--       Enter actions to be done in the u-tendency term here
683
684
685       CASE ( 'v-tendency' )
686
687
688       CASE ( 'w-tendency' )
689
690
691       CASE ( 'pt-tendency' )
692
693
694       CASE ( 'sa-tendency' )
695
696
697       CASE ( 'e-tendency' )
698
699
700       CASE ( 'q-tendency' )
701
702
703       CASE ( 's-tendency' )
704
705
706       CASE DEFAULT
707          CONTINUE
708
709    END SELECT
710
711    CALL cpu_log( log_point(24), 'user_actions', 'stop' )
712
713 END SUBROUTINE user_actions
714
715
716!--------------------------------------------------------------------------------------------------!
717! Description:
718! ------------
719!> Call for grid point i,j
720!--------------------------------------------------------------------------------------------------!
721 SUBROUTINE user_actions_ij( i, j, location )
722
723
724    CHARACTER(LEN=*) ::  location  !<
725
726    INTEGER(iwp) ::  i  !<
727    INTEGER(iwp) ::  j  !<
728
729!
730!-- Here the user-defined actions follow
731    SELECT CASE ( location )
732
733       CASE ( 'u-tendency' )
734
735!
736!--       Next line is to avoid compiler warning about unused variables. Please remove.
737          IF ( i == 0  .OR.  j == 0 )  CONTINUE
738
739!
740!--       Enter actions to be done in the u-tendency term here
741
742
743       CASE ( 'v-tendency' )
744
745
746       CASE ( 'w-tendency' )
747
748
749       CASE ( 'pt-tendency' )
750
751
752       CASE ( 'sa-tendency' )
753
754
755       CASE ( 'e-tendency' )
756
757
758       CASE ( 'q-tendency' )
759
760
761       CASE ( 's-tendency' )
762
763
764       CASE DEFAULT
765          CONTINUE
766
767    END SELECT
768
769 END SUBROUTINE user_actions_ij
770
771
772!--------------------------------------------------------------------------------------------------!
773! Description:
774! ------------
775!> Sum up and time-average user-defined output quantities as well as allocate the array necessary
776!> for storing the average.
777!--------------------------------------------------------------------------------------------------!
778 SUBROUTINE user_3d_data_averaging( mode, variable )
779
780
781    CHARACTER(LEN=*) ::  mode      !<
782    CHARACTER(LEN=*) ::  variable  !<
783
784    INTEGER(iwp) ::  i  !<
785    INTEGER(iwp) ::  j  !<
786    INTEGER(iwp) ::  k  !<
787
788    IF ( mode == 'allocate' )  THEN
789
790       SELECT CASE ( TRIM( variable ) )
791
792!
793!--       Uncomment and extend the following lines, if necessary.
794!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
795!--       defined by the user!
796!--       Sample for user-defined output:
797!          CASE ( 'u2' )
798!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
799!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
800!             ENDIF
801!             u2_av = 0.0_wp
802
803          CASE ( 'v_h' )
804             IF ( .NOT. ALLOCATED( v_h_av ) )  THEN
805                ALLOCATE( v_h_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
806             ENDIF
807             v_h_av = 0.0_wp
808
809          CASE DEFAULT
810             CONTINUE
811
812       END SELECT
813
814    ELSEIF ( mode == 'sum' )  THEN
815
816       SELECT CASE ( TRIM( variable ) )
817
818!
819!--       Uncomment and extend the following lines, if necessary.
820!--       The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
821!--       and defined by the user!
822!--       Sample for user-defined output:
823!          CASE ( 'u2' )
824!             IF ( ALLOCATED( u2_av ) )  THEN
825!                DO  i = nxlg, nxrg
826!                   DO  j = nysg, nyng
827!                      DO  k = nzb, nzt+1
828!                         u2_av(k,j,i) = u2_av(k,j,i) + u2(k,j,i)
829!                      ENDDO
830!                   ENDDO
831!                ENDDO
832!             ENDIF
833
834          CASE ( 'v_h' )
835
836             IF ( ALLOCATED( v_h_av ) ) THEN
837                DO  i = nxlg, nxrg
838                   DO  j = nysg, nyng
839                      DO  k = nzb, nzt+1
840                         v_h_av(k,j,i) = v_h_av(k,j,i) + v_h(k,j,i)
841                      ENDDO
842                   ENDDO
843                ENDDO
844             ENDIF
845
846
847          CASE DEFAULT
848             CONTINUE
849
850       END SELECT
851
852    ELSEIF ( mode == 'average' )  THEN
853
854       SELECT CASE ( TRIM( variable ) )
855
856!
857!--       Uncomment and extend the following lines, if necessary.
858!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
859!--       defined by the user!
860!--       Sample for user-defined output:
861!          CASE ( 'u2' )
862!             IF ( ALLOCATED( u2_av ) )  THEN
863!                DO  i = nxlg, nxrg
864!                   DO  j = nysg, nyng
865!                      DO  k = nzb, nzt+1
866!                         u2_av(k,j,i) = u2_av(k,j,i) / REAL( average_count_3d, KIND=wp )
867!                      ENDDO
868!                   ENDDO
869!                ENDDO
870!             ENDIF
871
872          CASE ( 'v_h' )
873
874             IF ( ALLOCATED( v_h_av ) ) THEN
875                DO  i = nxlg, nxrg
876                   DO  j = nysg, nyng
877                      DO  k = nzb, nzt+1
878                         v_h_av(k,j,i) = v_h_av(k,j,i) / REAL( average_count_3d, KIND=wp )
879                      ENDDO
880                   ENDDO
881                ENDDO
882             ENDIF
883
884
885       END SELECT
886
887    ENDIF
888
889
890 END SUBROUTINE user_3d_data_averaging
891
892
893!--------------------------------------------------------------------------------------------------!
894! Description:
895! ------------
896!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
897!> (i,j,k) and sets the grid on which it is defined. Allowed values for grid are "zu" and "zw".
898!--------------------------------------------------------------------------------------------------!
899 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do )
900
901
902    CHARACTER(LEN=*) ::  grid      !<
903    CHARACTER(LEN=*) ::  variable  !<
904
905    INTEGER(iwp) ::  av      !< flag to control data output of instantaneous or time-averaged data
906    INTEGER(iwp) ::  i       !< grid index along x-direction
907    INTEGER(iwp) ::  j       !< grid index along y-direction
908    INTEGER(iwp) ::  k       !< grid index along z-direction
909!    INTEGER(iwp) ::  m       !< running index surface elements
910    INTEGER(iwp) ::  nzb_do  !< lower limit of the domain (usually nzb)
911    INTEGER(iwp) ::  nzt_do  !< upper limit of the domain (usually nzt+1)
912
913    LOGICAL      ::  found  !<
914    LOGICAL      ::  two_d  !< flag parameter that indicates 2D variables (horizontal cross sections)
915
916   REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
917
918    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
919
920!
921!-- Next line is to avoid compiler warning about unused variables. Please remove.
922    IF ( av == 0  .OR.  local_pf(nxl,nys,nzb_do) == 0.0_wp  .OR.  two_d )  CONTINUE
923
924
925    found = .TRUE.
926
927    SELECT CASE ( TRIM( variable ) )
928
929!
930!--    Uncomment and extend the following lines, if necessary.
931!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
932!--    and defined by the user!
933!--    Sample for user-defined output:
934!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
935!          IF ( av == 0 )  THEN
936!             DO  i = nxl, nxr
937!                DO  j = nys, nyn
938!                   DO  k = nzb_do, nzt_do
939!                      local_pf(i,j,k) = u2(k,j,i)
940!                   ENDDO
941!                ENDDO
942!             ENDDO
943!          ELSE
944!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
945!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
946!                u2_av = REAL( fill_value, KIND = wp )
947!             ENDIF
948!             DO  i = nxl, nxr
949!                DO  j = nys, nyn
950!                   DO  k = nzb_do, nzt_do
951!                      local_pf(i,j,k) = u2_av(k,j,i)
952!                   ENDDO
953!                ENDDO
954!             ENDDO
955!          ENDIF
956!
957!          grid = 'zu'
958
959       CASE ( 'v_h_xy', 'v_h_xz', 'v_h_yz' )
960          IF ( av == 0 )  THEN
961             DO  i = nxl, nxr
962                DO  j = nys, nyn
963                   DO  k = nzb_do, nzt_do
964                      local_pf(i,j,k) = v_h(k,j,i)
965                   ENDDO
966                ENDDO
967             ENDDO
968          ELSE
969             IF ( .NOT. ALLOCATED( v_h_av ) ) THEN
970                ALLOCATE( v_h_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
971                v_h_av = REAL( fill_value, KIND = wp )
972             ENDIF
973             DO  i = nxl, nxr
974                DO  j = nys, nyn
975                   DO  k = nzb_do, nzt_do
976                      local_pf(i,j,k) = v_h_av(k,j,i)
977                   ENDDO
978                ENDDO
979             ENDDO
980          ENDIF
981
982          grid = 'zu'
983
984!
985!--    In case two-dimensional surface variables are output, the user has to access related
986!--    surface-type. Uncomment and extend following lines appropriately (example output of vertical
987!--    surface momentum flux of u-component). Please note, surface elements can be distributed over
988!--    several data types, depending on their respective surface properties.
989!       CASE ( 'usws_xy' )
990!          IF ( av == 0 )  THEN
991!
992!--           Horizontal default-type surfaces
993!             DO  m = 1, surf_def_h(0)%ns
994!                i = surf_def_h(0)%i(m)
995!                j = surf_def_h(0)%j(m)
996!                local_pf(i,j,1) = surf_def_h(0)%usws(m)
997!             ENDDO
998!
999!--           Horizontal natural-type surfaces
1000!             DO  m = 1, surf_lsm_h%ns
1001!                i = surf_lsm_h%i(m)
1002!                j = surf_lsm_h%j(m)
1003!                local_pf(i,j,1) = surf_lsm_h%usws(m)
1004!             ENDDO
1005!
1006!--           Horizontal urban-type surfaces
1007!             DO  m = 1, surf_usm_h%ns
1008!                i = surf_usm_h%i(m)
1009!                j = surf_usm_h%j(m)
1010!                local_pf(i,j,1) = surf_usm_h%usws(m)
1011!             ENDDO
1012!          ENDIF
1013!
1014!          grid = 'zu'
1015!--
1016
1017
1018       CASE DEFAULT
1019          found = .FALSE.
1020          grid  = 'none'
1021
1022    END SELECT
1023
1024
1025 END SUBROUTINE user_data_output_2d
1026
1027
1028!--------------------------------------------------------------------------------------------------!
1029! Description:
1030! ------------
1031!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
1032!> (i,j,k).
1033!--------------------------------------------------------------------------------------------------!
1034 SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1035
1036
1037    CHARACTER(LEN=*) ::  variable  !<
1038
1039    INTEGER(iwp) ::  av     !<
1040    INTEGER(iwp) ::  i      !<
1041    INTEGER(iwp) ::  j      !<
1042    INTEGER(iwp) ::  k      !<
1043    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
1044    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
1045
1046    LOGICAL      ::  found  !<
1047
1048   REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
1049
1050    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
1051
1052!
1053!-- Next line is to avoid compiler warning about unused variables. Please remove.
1054    IF ( av == 0  .OR.  local_pf(nxl,nys,nzb_do) == 0.0_wp )  CONTINUE
1055
1056
1057    found = .TRUE.
1058
1059    SELECT CASE ( TRIM( variable ) )
1060
1061!
1062!--    Uncomment and extend the following lines, if necessary.
1063!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
1064!--    and defined by the user!
1065!--    Sample for user-defined output:
1066!       CASE ( 'u2' )
1067!          IF ( av == 0 )  THEN
1068!             DO  i = nxl, nxr
1069!                DO  j = nys, nyn
1070!                   DO  k = nzb_do, nzt_do
1071!                      local_pf(i,j,k) = u2(k,j,i)
1072!                   ENDDO
1073!                ENDDO
1074!             ENDDO
1075!          ELSE
1076!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
1077!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1078!                u2_av = REAL( fill_value, KIND = wp )
1079!             ENDIF
1080!             DO  i = nxl, nxr
1081!                DO  j = nys, nyn
1082!                   DO  k = nzb_do, nzt_do
1083!                      local_pf(i,j,k) = u2_av(k,j,i)
1084!                   ENDDO
1085!                ENDDO
1086!             ENDDO
1087!          ENDIF
1088
1089       CASE ( 'v_h' )
1090          IF ( av == 0 )  THEN
1091             DO  i = nxl, nxr
1092                DO  j = nys, nyn
1093                   DO  k = nzb_do, nzt_do
1094                      local_pf(i,j,k) = v_h(k,j,i)
1095                   ENDDO
1096                ENDDO
1097             ENDDO
1098          ELSE
1099             IF ( .NOT. ALLOCATED( v_h_av ) ) THEN
1100                ALLOCATE( v_h_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1101                v_h_av = REAL( fill_value, KIND = wp )
1102             ENDIF
1103             DO  i = nxl, nxr
1104                DO  j = nys, nyn
1105                   DO  k = nzb_do, nzt_do
1106                      local_pf(i,j,k) = v_h_av(k,j,i)
1107                   ENDDO
1108                ENDDO
1109             ENDDO
1110          ENDIF
1111
1112
1113       CASE DEFAULT
1114          found = .FALSE.
1115
1116    END SELECT
1117
1118
1119 END SUBROUTINE user_data_output_3d
1120
1121
1122!--------------------------------------------------------------------------------------------------!
1123! Description:
1124! ------------
1125!> Calculation of user-defined statistics, i.e. horizontally averaged profiles and time series.
1126!> This routine is called for every statistic region sr defined by the user, but at least for the
1127!> region "total domain" (sr=0). See section 3.5.4 on how to define, calculate, and output user
1128!> defined quantities.
1129!--------------------------------------------------------------------------------------------------!
1130 SUBROUTINE user_statistics( mode, sr, tn )
1131
1132
1133    CHARACTER(LEN=*) ::  mode  !<
1134!    INTEGER(iwp) ::  i   !<
1135!    INTEGER(iwp) ::  j   !<
1136!    INTEGER(iwp) ::  k   !<
1137    INTEGER(iwp) ::  sr  !<
1138    INTEGER(iwp) ::  tn  !<
1139
1140!    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l  !<
1141
1142!
1143!-- Next line is to avoid compiler warning about unused variables. Please remove.
1144    IF ( sr == 0  .OR.  tn == 0 )  CONTINUE
1145
1146    IF ( mode == 'profiles' )  THEN
1147
1148!
1149!--    Sample on how to calculate horizontally averaged profiles of user-defined quantities. Each
1150!--    quantity is identified by the index "pr_palm+#" where "#" is an integer starting from 1.
1151!--    These user-profile-numbers must also be assigned to the respective strings given by
1152!--    data_output_pr_user in routine user_check_data_output_pr.
1153!       !$OMP DO
1154!       DO  i = nxl, nxr
1155!          DO  j = nys, nyn
1156!             DO  k = nzb+1, nzt
1157!!
1158!!--             Sample on how to calculate the profile of the resolved-scale horizontal momentum
1159!!--             flux u*v*
1160!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +                                  &
1161!                                         ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *  &
1162!                                         ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) *  &
1163!                                         rmask(j,i,sr) * MERGE( 1.0_wp, 0.0_wp,                    &
1164!                                         BTEST( wall_flags_total_0(k,j,i), 0 ) )
1165!!
1166!!--             Further profiles can be defined and calculated by increasing the second index of
1167!!--             array sums_l (replace ... appropriately)
1168!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...   * rmask(j,i,sr)
1169!             ENDDO
1170!          ENDDO
1171!       ENDDO
1172
1173    ELSEIF ( mode == 'time_series' )  THEN
1174
1175
1176!       ALLOCATE ( ts_value_l(dots_num_user) )
1177!
1178!--    Sample on how to add values for the user-defined time series quantities.
1179!--    These have to be defined before in routine user_init. This sample creates two time series for
1180!--    the absolut values of the horizontal velocities u and v.
1181!       ts_value_l = 0.0_wp
1182!       ts_value_l(1) = ABS( u_max )
1183!       ts_value_l(2) = ABS( v_max )
1184!
1185!--     Collect / send values to PE0, because only PE0 outputs the time series.
1186!--     CAUTION: Collection is done by taking the sum over all processors. You may have to normalize
1187!--              this sum, depending on the quantity that you like to calculate. For serial runs,
1188!--              nothing has to be done.
1189!--     HINT: If the time series value that you are calculating has the same value on all PEs, you
1190!--           can omit the MPI_ALLREDUCE call and assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
1191!#if defined( __parallel )
1192!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
1193!       CALL MPI_ALLREDUCE( ts_value_l(1), ts_value(dots_num_palm+1,sr), dots_num_user, MPI_REAL,   &
1194!                           MPI_MAX, comm2d, ierr )
1195!#else
1196!       ts_value(dots_num_palm+1:dots_num_palm+dots_num_user,sr) = ts_value_l
1197!#endif
1198
1199    ENDIF
1200
1201 END SUBROUTINE user_statistics
1202
1203
1204!--------------------------------------------------------------------------------------------------!
1205! Description:
1206! ------------
1207!> Read module-specific global restart data (Fortran binary format).
1208!--------------------------------------------------------------------------------------------------!
1209 SUBROUTINE user_rrd_global_ftn( found )
1210
1211
1212    LOGICAL, INTENT(OUT)  ::  found  !<
1213
1214
1215    found = .TRUE.
1216
1217
1218    SELECT CASE ( restart_string(1:length) )
1219
1220       CASE ( 'global_paramter' )
1221!          READ ( 13 )  global_parameter
1222
1223       CASE DEFAULT
1224
1225          found = .FALSE.
1226
1227    END SELECT
1228
1229
1230 END SUBROUTINE user_rrd_global_ftn
1231
1232
1233!--------------------------------------------------------------------------------------------------!
1234! Description:
1235! ------------
1236!> Read module-specific global restart data (MPI-IO).
1237!--------------------------------------------------------------------------------------------------!
1238 SUBROUTINE user_rrd_global_mpi
1239
1240!    USE restart_data_mpi_io_mod,                                                                   &
1241!        ONLY:  rrd_mpi_io
1242
1243!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
1244    CONTINUE
1245
1246 END SUBROUTINE user_rrd_global_mpi
1247
1248
1249!--------------------------------------------------------------------------------------------------!
1250! Description:
1251! ------------
1252!> Read module-specific local restart data arrays (Fortran binary format).
1253!> Subdomain
1254!> index limits on file are given by nxl_on_file, etc. Indices nxlc, etc. indicate the range of
1255!> gridpoints to be mapped from the subdomain on file (f) to the subdomain of the current PE (c).
1256!> They have been calculated in routine rrd_local.
1257!--------------------------------------------------------------------------------------------------!
1258 SUBROUTINE user_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,   &
1259                                nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
1260
1261
1262    INTEGER(iwp) ::  idum            !<
1263    INTEGER(iwp) ::  k               !<
1264    INTEGER(iwp) ::  nxlc            !<
1265    INTEGER(iwp) ::  nxlf            !<
1266    INTEGER(iwp) ::  nxl_on_file     !<
1267    INTEGER(iwp) ::  nxrc            !<
1268    INTEGER(iwp) ::  nxrf            !<
1269    INTEGER(iwp) ::  nxr_on_file     !<
1270    INTEGER(iwp) ::  nync            !<
1271    INTEGER(iwp) ::  nynf            !<
1272    INTEGER(iwp) ::  nyn_on_file     !<
1273    INTEGER(iwp) ::  nysc            !<
1274    INTEGER(iwp) ::  nysf            !<
1275    INTEGER(iwp) ::  nys_on_file     !<
1276
1277    LOGICAL, INTENT(OUT)  ::  found  !<
1278
1279    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d  !<
1280
1281!
1282!-- Next line is to avoid compiler warning about unused variables. Please remove.
1283    idum = k + nxlc + nxlf + nxrc + nxrf + nync + nynf + nysc + nysf +                             &
1284           INT( tmp_3d(nzb,nys_on_file,nxl_on_file) )
1285
1286!
1287!-- Here the reading of user-defined restart data follows:
1288!-- Sample for user-defined output
1289
1290    found = .TRUE.
1291
1292    SELECT CASE ( restart_string(1:length) )
1293
1294       CASE ( 'u2_av' )
1295!          IF ( .NOT. ALLOCATED( u2_av ) )  THEN
1296!               ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1297!          ENDIF
1298!          IF ( k == 1 )  READ ( 13 )  tmp_3d
1299!             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                    &
1300!             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1301!
1302       CASE DEFAULT
1303
1304          found = .FALSE.
1305
1306    END SELECT
1307
1308 END SUBROUTINE user_rrd_local_ftn
1309
1310
1311!--------------------------------------------------------------------------------------------------!
1312! Description:
1313! ------------
1314!> Read module-specific local restart data arrays (MPI-IO).
1315!--------------------------------------------------------------------------------------------------!
1316 SUBROUTINE user_rrd_local_mpi
1317
1318!    USE restart_data_mpi_io_mod,                                                                   &
1319!        ONLY:  rd_mpi_io_check_array, rrd_mpi_io
1320
1321!    CALL rd_mpi_io_check_array( 'u2_av' , found = array_found )
1322!    IF ( array_found )  THEN
1323!       IF ( .NOT. ALLOCATED( u2_av ) )  ALLOCATE( u2_av(nysg:nyng,nxlg:nxrg) )
1324!       CALL rrd_mpi_io( 'rad_u2_av', rad_u2_av )
1325!    ENDIF
1326
1327    CONTINUE
1328
1329 END SUBROUTINE user_rrd_local_mpi
1330
1331
1332!--------------------------------------------------------------------------------------------------!
1333! Description:
1334! ------------
1335!> Writes global and user-defined restart data into binary file(s) for restart runs.
1336!--------------------------------------------------------------------------------------------------!
1337 SUBROUTINE user_wrd_global
1338
1339!    USE restart_data_mpi_io_mod,                                                                   &
1340!        ONLY:  wrd_mpi_io
1341
1342    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
1343
1344!       CALL wrd_write_string( 'global_parameter' )
1345!       WRITE ( 14 )  global_parameter
1346
1347    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
1348
1349!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
1350
1351    ENDIF
1352
1353 END SUBROUTINE user_wrd_global
1354
1355
1356!--------------------------------------------------------------------------------------------------!
1357! Description:
1358! ------------
1359!> Writes processor specific and user-defined restart data into binary file(s) for restart runs.
1360!--------------------------------------------------------------------------------------------------!
1361 SUBROUTINE user_wrd_local
1362
1363!    USE restart_data_mpi_io_mod,                                                                   &
1364!        ONLY:  wrd_mpi_io
1365
1366!
1367!-- Here the user-defined actions at the end of a job follow.
1368!-- Sample for user-defined output:
1369    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
1370
1371!       IF ( ALLOCATED( u2_av ) )  THEN
1372!          CALL wrd_write_string( 'u2_av' )
1373!          WRITE ( 14 )  u2_av
1374!       ENDIF
1375
1376    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
1377
1378!       IF ( ALLOCATED( u2_av ) )  CALL wrd_mpi_io( 'u2_av', u2_av )
1379
1380    ENDIF
1381
1382 END SUBROUTINE user_wrd_local
1383
1384
1385!--------------------------------------------------------------------------------------------------!
1386! Description:
1387! ------------
1388!> Execution of user-defined actions at the end of a job.
1389!--------------------------------------------------------------------------------------------------!
1390 SUBROUTINE user_last_actions
1391
1392!
1393!-- Here the user-defined actions at the end of a job might follow.
1394
1395
1396 END SUBROUTINE user_last_actions
1397
1398 END MODULE user
Note: See TracBrowser for help on using the repository browser.