source: palm/trunk/TUTORIALS/cases/dispersion_eulerian_and_lpm_extended/USER_CODE/user_module.f90 @ 4398

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

bugfixes for previous commit: unused variables removed, Temperton-fft usage on GPU, openacc porting of vector version of Obukhov length calculation, collective read switched off on NEC to avoid hanging; some vector directives added in prognostic equations to force vectorization on Intel19 compiler, configuration files for NEC Aurora added

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