source: palm/trunk/SOURCE/user_interface.f90 @ 132

Last change on this file since 132 was 130, checked in by letzel, 16 years ago

DVRP output modifications:

  • The user can now visualize user-defined quantities using dvrp.

data_output_dvrp calls the new user_interface subroutine
user_data_output_dvrp in case of unknown variables (CASE DEFAULT).

  • Two instead of one digit are allowed to specify isosurface and slicer

variables with the parameter mode_dvrp.

  • Property svn:keywords set to Id
File size: 28.4 KB
Line 
1 MODULE user
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! new subroutine user_data_output_dvrp
7! +argument gls in user_init_grid
8!
9! Former revisions:
10! -----------------
11! $Id: user_interface.f90 130 2007-11-13 14:08:40Z letzel $
12!
13! 105 2007-08-08 07:12:55Z raasch
14! +dots_num_palm in module user, +module netcdf_control in user_init
15!
16! 95 2007-06-02 16:48:38Z raasch
17! user action for salinity added
18!
19! 89 2007-05-25 12:08:31Z raasch
20! Calculation and output of user-defined profiles: new routine
21! user_check_data_output_pr, +data_output_pr_user, max_pr_user in userpar,
22! routine user_statistics has got two more arguments
23! Bugfix: field_chr renamed field_char
24!
25! 60 2007-03-11 11:50:04Z raasch
26! New routine user_init_3d_model which allows the initial setting of all 3d
27! arrays under control of the user, new routine user_advec_particles,
28! routine user_statistics now has one argument (sr),
29! sample for generating time series quantities added
30! Bugfix in sample for reading user defined data from restart file (user_init)
31!
32! RCS Log replace by Id keyword, revision history cleaned up
33!
34! Revision 1.18  2006/06/02 15:25:00  raasch
35! +change of grid-defining arguments in routine user_define_netcdf_grid,
36! new argument "found" in user_data_output_2d and user_data_output_3d
37!
38! Revision 1.1  1998/03/24 15:29:04  raasch
39! Initial revision
40!
41!
42! Description:
43! ------------
44! Declaration of user-defined variables. This module may only be used
45! in the user-defined routines (contained in user_interface.f90).
46!------------------------------------------------------------------------------!
47
48    INTEGER ::  dots_num_palm, user_idummy
49    LOGICAL ::  user_defined_namelist_found = .FALSE.
50    REAL    ::  user_dummy
51
52!
53!-- Sample for user-defined output
54!    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  u2, u2_av
55
56    SAVE
57
58 END MODULE user
59
60
61 SUBROUTINE user_parin
62
63!------------------------------------------------------------------------------!
64!
65! Description:
66! ------------
67! Interface to read user-defined namelist-parameters.
68!------------------------------------------------------------------------------!
69
70    USE control_parameters
71    USE pegrid
72    USE statistics
73    USE user
74
75    IMPLICIT NONE
76
77    CHARACTER (LEN=80) ::  zeile
78
79    INTEGER ::  i, j
80
81
82    NAMELIST /userpar/  data_output_pr_user, data_output_user, region
83
84!
85!-- Position the namelist-file at the beginning (it was already opened in
86!-- parin), search for user-defined namelist-group ("userpar", but any other
87!-- name can be choosed) and position the file at this line.
88    REWIND ( 11 )
89
90    zeile = ' '
91    DO   WHILE ( INDEX( zeile, '&userpar' ) == 0 )
92       READ ( 11, '(A)', END=100 )  zeile
93    ENDDO
94    BACKSPACE ( 11 )
95
96!
97!-- Read user-defined namelist
98    READ ( 11, userpar )
99    user_defined_namelist_found = .TRUE.
100
101!
102!-- Determine the number of user-defined profiles and append them to the
103!-- standard data output (data_output_pr)
104    IF ( data_output_pr_user(1) /= ' ' )  THEN
105       i = 1
106       DO  WHILE ( data_output_pr(i) /= ' '  .AND.  i <= 100 )
107          i = i + 1
108       ENDDO
109       j = 1
110       DO  WHILE ( data_output_pr_user(j) /= ' '  .AND.  j <= 100 )
111          data_output_pr(i) = data_output_pr_user(j)
112          max_pr_user       = max_pr_user + 1
113          i = i + 1
114          j = j + 1
115       ENDDO
116    ENDIF
117
118100 RETURN
119
120 END SUBROUTINE user_parin
121
122
123
124 SUBROUTINE user_header( io )
125
126!------------------------------------------------------------------------------!
127!
128! Description:
129! ------------
130! Print a header with user-defined informations.
131!------------------------------------------------------------------------------!
132
133    USE statistics
134    USE user
135
136    IMPLICIT NONE
137
138    INTEGER ::  i, io
139
140!
141!-- If no user-defined variables are read from the namelist-file, no
142!-- informations will be printed.
143    IF ( .NOT. user_defined_namelist_found )  THEN
144       WRITE ( io, 100 )
145       RETURN
146    ENDIF
147
148!
149!-- Printing the informations.
150    WRITE ( io, 110 )
151
152    IF ( statistic_regions /= 0 )  THEN
153       WRITE ( io, 200 )
154       DO  i = 0, statistic_regions
155          WRITE ( io, 201 )  i, region(i)
156       ENDDO
157    ENDIF
158
159
160
161!
162!-- Format-descriptors
163100 FORMAT (//' *** no user-defined variables found'/)
164110 FORMAT (//1X,78('#')                                      &
165            //' User-defined variables and actions:'/  &
166              ' -----------------------------------'//)
167200 FORMAT (' Output of profiles and time series for following regions:' /)
168201 FORMAT (4X,'Region ',I1,':   ',A)
169
170
171 END SUBROUTINE user_header
172
173
174
175 SUBROUTINE user_init
176
177!------------------------------------------------------------------------------!
178!
179! Description:
180! ------------
181! Execution of user-defined initializing actions
182!------------------------------------------------------------------------------!
183
184    USE control_parameters
185    USE indices
186    USE netcdf_control
187    USE pegrid
188    USE user
189
190    IMPLICIT NONE
191
192    CHARACTER (LEN=20) :: field_char
193!
194!-- Here the user-defined initializing actions follow:
195!-- Sample for user-defined output
196!    ALLOCATE( u2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
197!
198!    IF ( initializing_actions == 'read_restart_data' )  THEN
199!       READ ( 13 )  field_char
200!       DO  WHILE ( TRIM( field_char ) /= '*** end user ***' )
201!
202!          SELECT CASE ( TRIM( field_char ) )
203!
204!             CASE ( 'u2_av' )
205!                ALLOCATE( u2_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
206!                READ ( 13 )  u2_av
207!
208!             CASE DEFAULT
209!                PRINT*, '+++ user_init: unknown variable named "', &
210!                        TRIM( field_char ), '" found in'
211!                PRINT*, '               data from prior run on PE ', myid
212!                CALL local_stop
213!
214!          END SELECT
215!
216!          READ ( 13 )  field_char
217!
218!       ENDDO
219!    ENDIF
220
221!
222!-- Sample for user-defined time series
223!-- For each time series quantity you have to give a label and a unit,
224!-- which will be used for the NetCDF file. They must not contain more than
225!-- seven characters. The value of dots_num has to be increased by the
226!-- number of new time series quantities. Its old value has to be store in
227!-- dots_num_palm. See routine user_statistics on how to output calculate
228!-- and output these quantities.
229!    dots_label(dots_num+1) = 'abs_umx'
230!    dots_unit(dots_num+1)  = 'm/s'
231!    dots_label(dots_num+2) = 'abs_vmx'
232!    dots_unit(dots_num+2)  = 'm/s'
233!
234!    dots_num_palm = dots_num
235!    dots_num = dots_num + 2
236
237 END SUBROUTINE user_init
238
239
240
241 SUBROUTINE user_init_grid( gls, nzb_local )
242
243!------------------------------------------------------------------------------!
244!
245! Description:
246! ------------
247! Execution of user-defined grid initializing actions
248! First argument gls contains the number of ghost layers, which is > 1 if the
249! multigrid method for the pressure solver is used
250!------------------------------------------------------------------------------!
251
252    USE control_parameters
253    USE indices
254    USE user
255
256    IMPLICIT NONE
257
258    INTEGER ::  gls
259
260    INTEGER, DIMENSION(-gls:ny+gls,-gls:nx+gls) ::  nzb_local
261
262!
263!-- Here the user-defined grid initializing actions follow:
264
265!
266!-- Set the index array nzb_local for non-flat topography.
267!-- Here consistency checks concerning domain size and periodicity are necessary
268    SELECT CASE ( TRIM( topography ) )
269
270       CASE ( 'flat', 'single_building' )
271!
272!--       Not allowed here since these are the standard cases used in init_grid.
273
274       CASE ( 'user_defined_topography_1' )
275!
276!--       Here the user can define his own topography. After definition, please
277!--       remove the following three lines!
278          PRINT*, '+++ user_init_grid: topography "', &
279               topography, '" not available yet'
280          CALL local_stop
281
282       CASE DEFAULT
283!
284!--       The DEFAULT case is reached if the parameter topography contains a
285!--       wrong character string that is neither recognized in init_grid nor
286!--       here in user_init_grid.
287          PRINT*, '+++ (user_)init_grid: unknown topography "', &
288               topography, '"'
289          CALL local_stop
290
291    END SELECT
292
293
294 END SUBROUTINE user_init_grid
295
296
297
298 SUBROUTINE user_init_3d_model
299
300!------------------------------------------------------------------------------!
301!
302! Description:
303! ------------
304! Allows the complete initialization of the 3d model.
305!
306! CAUTION: The user is responsible to set at least all those quantities which
307! ------   are normally set within init_3d_model!
308!------------------------------------------------------------------------------!
309
310    USE arrays_3d
311    USE control_parameters
312    USE indices
313    USE user
314
315    IMPLICIT NONE
316
317
318 END SUBROUTINE user_init_3d_model
319
320
321
322 MODULE user_actions_mod
323
324!------------------------------------------------------------------------------!
325!
326! Description:
327! ------------
328! Execution of user-defined actions before or after single timesteps
329!------------------------------------------------------------------------------!
330
331    PRIVATE
332    PUBLIC user_actions
333
334    INTERFACE user_actions
335       MODULE PROCEDURE user_actions
336       MODULE PROCEDURE user_actions_ij
337    END INTERFACE user_actions
338
339 CONTAINS
340
341
342!------------------------------------------------------------------------------!
343! Call for all grid points
344!------------------------------------------------------------------------------!
345    SUBROUTINE user_actions( location )
346
347       USE control_parameters
348       USE cpulog
349       USE indices
350       USE interfaces
351       USE pegrid
352       USE user
353       USE arrays_3d
354
355       IMPLICIT NONE
356
357       CHARACTER (LEN=*) ::  location
358
359       INTEGER ::  i, j, k
360
361       CALL cpu_log( log_point(24), 'user_actions', 'start' )
362
363!
364!--    Here the user-defined actions follow
365!--    No calls for single grid points are allowed at locations before and
366!--    after the timestep, since these calls are not within an i,j-loop
367       SELECT CASE ( location )
368
369          CASE ( 'before_timestep' )
370!
371!--          Enter actions to be done before every timestep here
372
373
374          CASE ( 'after_integration' )
375!
376!--          Enter actions to be done after every time integration (before
377!--          data output)
378!--          Sample for user-defined output:
379!             DO  i = nxl-1, nxr+1
380!                DO  j = nys-1, nyn+1
381!                   DO  k = nzb, nzt+1
382!                      u2(k,j,i) = u(k,j,i)**2
383!                   ENDDO
384!                ENDDO
385!             ENDDO
386
387
388          CASE ( 'after_timestep' )
389!
390!--          Enter actions to be done after every timestep here
391
392
393          CASE ( 'u-tendency' )
394!
395!--          Enter actions to be done in the u-tendency term here
396
397
398          CASE ( 'v-tendency' )
399
400
401          CASE ( 'w-tendency' )
402
403
404          CASE ( 'pt-tendency' )
405
406
407          CASE ( 'sa-tendency' )
408
409
410          CASE ( 'e-tendency' )
411
412
413          CASE ( 'q-tendency' )
414
415
416          CASE DEFAULT
417             IF ( myid == 0 )  PRINT*, '+++ user_actions: unknown location "', &
418                                       location, '"'
419             CALL local_stop
420
421       END SELECT
422
423       CALL cpu_log( log_point(24), 'user_actions', 'stop' )
424
425    END SUBROUTINE user_actions
426
427
428!------------------------------------------------------------------------------!
429! Call for grid point i,j
430!------------------------------------------------------------------------------!
431    SUBROUTINE user_actions_ij( i, j, location )
432
433       USE control_parameters
434       USE pegrid
435       USE user
436
437       IMPLICIT NONE
438
439       CHARACTER (LEN=*) ::  location
440
441       INTEGER ::  i, idum, j
442
443
444!
445!--    Here the user-defined actions follow
446       SELECT CASE ( location )
447
448          CASE ( 'u-tendency' )
449!
450!--          Enter actions to be done in the u-tendency term here
451
452
453          CASE ( 'v-tendency' )
454
455
456          CASE ( 'w-tendency' )
457
458
459          CASE ( 'pt-tendency' )
460
461
462          CASE ( 'sa-tendency' )
463
464
465          CASE ( 'e-tendency' )
466
467
468          CASE ( 'q-tendency' )
469
470
471          CASE ( 'before_timestep', 'after_integration', 'after_timestep' )
472             IF ( myid == 0 )  THEN
473                PRINT*, '+++ user_actions: location "', location, '" is not ', &
474                             'allowed to be called with parameters "i" and "j"'
475             ENDIF
476             CALL local_stop
477
478
479          CASE DEFAULT
480             IF ( myid == 0 )  PRINT*, '+++ user_actions: unknown location "', &
481                                       location, '"'
482             CALL local_stop
483
484
485       END SELECT
486
487    END SUBROUTINE user_actions_ij
488
489 END MODULE user_actions_mod
490
491
492
493 SUBROUTINE user_statistics( mode, sr, tn )
494
495!------------------------------------------------------------------------------!
496!
497! Description:
498! ------------
499! Calculation of user-defined statistics, i.e. horizontally averaged profiles
500! and time series.
501! This routine is called for every statistic region sr defined by the user,
502! but at least for the region "total domain" (sr=0).
503! See section 3.5.4 on how to define, calculate, and output user defined
504! quantities.
505!------------------------------------------------------------------------------!
506
507    USE arrays_3d
508    USE indices
509    USE statistics
510    USE user
511
512    IMPLICIT NONE
513
514    CHARACTER (LEN=*) ::  mode
515
516    INTEGER ::  i, j, k, sr, tn
517
518
519    IF ( mode == 'profiles' )  THEN
520
521!
522!--    Sample on how to calculate horizontally averaged profiles of user-
523!--    defined quantities. Each quantity is identified by the index
524!--    "pr_palm+#" where "#" is an integer starting from 1. These
525!--    user-profile-numbers must also be assigned to the respective strings
526!--    given by data_output_pr_user in routine user_check_data_output_pr.
527!       !$OMP DO
528!       DO  i = nxl, nxr
529!          DO  j = nys, nyn
530!             DO  k = nzb_s_outer(j,i)+1, nzt
531!!
532!!--             Sample on how to calculate the profile of the resolved-scale
533!!--             horizontal momentum flux u*v*
534!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +           &
535!                      ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) * &
536!                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) * &
537!                                                 * rmask(j,i,sr)
538!!
539!!--             Further profiles can be defined and calculated by increasing
540!!--             the second index of array sums_l (replace ... appropriately)
541!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ... &
542!                                         * rmask(j,i,sr)
543!             ENDDO
544!          ENDDO
545!       ENDDO
546
547    ELSEIF ( mode == 'time_series' )  THEN
548
549!
550!--    Sample on how to add values for the user-defined time series quantities.
551!--    These have to be defined before in routine user_init. This sample
552!--    creates two time series for the absolut values of the horizontal
553!--    velocities u and v.
554!       ts_value(dots_num_palm+1,sr) = ABS( u_max )
555!       ts_value(dots_num_palm+2,sr) = ABS( v_max )
556
557    ENDIF
558
559 END SUBROUTINE user_statistics
560
561
562
563 SUBROUTINE user_last_actions
564
565!------------------------------------------------------------------------------!
566!
567! Description:
568! ------------
569! Execution of user-defined actions at the end of a job.
570!------------------------------------------------------------------------------!
571
572    USE user
573
574    IMPLICIT NONE
575
576!
577!-- Here the user-defined actions at the end of a job follow.
578!-- Sample for user-defined output:
579!    IF ( ALLOCATED( u2_av ) )  THEN
580!       WRITE ( 14 )  'u2_av               ';  WRITE ( 14 )  u2_av
581!    ENDIF
582
583    WRITE ( 14 )  '*** end user ***    '
584
585 END SUBROUTINE user_last_actions
586
587
588
589 SUBROUTINE user_init_particles
590
591!------------------------------------------------------------------------------!
592!
593! Description:
594! ------------
595! Modification of initial particles by the user.
596!------------------------------------------------------------------------------!
597
598    USE particle_attributes
599    USE user
600
601    IMPLICIT NONE
602
603    INTEGER ::  n
604
605!
606!-- Here the user-defined actions follow
607!    DO  n = 1, number_of_initial_particles
608!    ENDDO
609
610 END SUBROUTINE user_init_particles
611
612
613
614 SUBROUTINE user_advec_particles
615
616!------------------------------------------------------------------------------!
617!
618! Description:
619! ------------
620! Modification of initial particles by the user.
621!------------------------------------------------------------------------------!
622
623    USE particle_attributes
624    USE user
625
626    IMPLICIT NONE
627
628    INTEGER ::  n
629
630!
631!-- Here the user-defined actions follow
632!    DO  n = 1, number_of_initial_particles
633!    ENDDO
634
635 END SUBROUTINE user_advec_particles
636
637
638
639 SUBROUTINE user_particle_attributes
640
641!------------------------------------------------------------------------------!
642!
643! Description:
644! ------------
645! Define the actual particle attributes (size, colour) by the user.
646!------------------------------------------------------------------------------!
647
648    USE particle_attributes
649    USE user
650
651    IMPLICIT NONE
652
653    INTEGER ::  n
654
655!
656!-- Here the user-defined actions follow
657!    DO  n = 1, number_of_initial_particles
658!    ENDDO
659
660 END SUBROUTINE user_particle_attributes
661
662
663
664 SUBROUTINE user_dvrp_coltab( mode, variable )
665
666!------------------------------------------------------------------------------!
667!
668! Description:
669! ------------
670! Definition of the colour table to be used by the dvrp software.
671!------------------------------------------------------------------------------!
672
673    USE dvrp_variables
674    USE pegrid
675    USE user
676
677    IMPLICIT NONE
678
679    CHARACTER (LEN=*) ::  mode
680    CHARACTER (LEN=*) ::  variable
681
682
683!
684!-- Here the user-defined actions follow
685    SELECT CASE ( mode )
686
687       CASE ( 'particles' )
688
689       CASE ( 'slicer' )
690
691       CASE DEFAULT
692          IF ( myid == 0 )  PRINT*, '+++ user_dvrp_coltab: unknown mode "', &
693                                    mode, '"'
694          CALL local_stop
695
696    END SELECT
697
698 END SUBROUTINE user_dvrp_coltab
699
700
701
702 SUBROUTINE user_check_data_output( variable, unit )
703
704!------------------------------------------------------------------------------!
705!
706! Description:
707! ------------
708! Set the unit of user defined output quantities. For those variables
709! not recognized by the user, the parameter unit is set to "illegal", which
710! tells the calling routine that the output variable is not defined and leads
711! to a program abort.
712!------------------------------------------------------------------------------!
713
714    USE user
715
716    IMPLICIT NONE
717
718    CHARACTER (LEN=*) ::  unit, variable
719
720
721    SELECT CASE ( TRIM( variable ) )
722
723!
724!--    Uncomment and extend the following lines, if necessary
725!       CASE ( 'u2' )
726!          unit = 'm2/s2'
727!
728       CASE DEFAULT
729          unit = 'illegal'
730
731    END SELECT
732
733
734 END SUBROUTINE user_check_data_output
735
736
737
738 SUBROUTINE user_check_data_output_pr( variable, var_count, unit )
739
740!------------------------------------------------------------------------------!
741!
742! Description:
743! ------------
744! Set the unit of user defined profile output quantities. For those variables
745! not recognized by the user, the parameter unit is set to "illegal", which
746! tells the calling routine that the output variable is not defined and leads
747! to a program abort.
748!------------------------------------------------------------------------------!
749
750    USE arrays_3d
751    USE indices
752    USE netcdf_control
753    USE profil_parameter
754    USE statistics
755    USE user
756
757    IMPLICIT NONE
758
759    CHARACTER (LEN=*) ::  unit, variable
760
761    INTEGER ::  index, var_count
762
763
764    SELECT CASE ( TRIM( variable ) )
765
766!
767!--    Uncomment and extend the following lines, if necessary.
768!--    Add additional CASE statements depending on the number of quantities
769!--    for which profiles are to be calculated. The respective calculations
770!--    to be performed have to be added in routine user_statistics.
771!--    The quantities are (internally) identified by a user-profile-number
772!--    (see variable "index" below). The first user-profile must be assigned
773!--    the number "pr_palm+1", the second one "pr_palm+2", etc. The respective
774!--    user-profile-numbers have also to be used in routine user_statistics!
775!       CASE ( 'u*v*' )                      ! quantity string as given in
776!                                            ! data_output_pr_user
777!          index = pr_palm + 1
778!          dopr_index(var_count)  = index    ! quantities' user-profile-number
779!          dopr_unit(var_count)   = 'm2/s2'  ! quantity unit
780!          hom(:,2,index,:)       = SPREAD( zu, 2, statistic_regions+1 )
781!                                            ! grid on which the quantity is
782!                                            ! defined (use zu or zw)
783
784       CASE DEFAULT
785          unit = 'illegal'
786
787    END SELECT
788
789
790 END SUBROUTINE user_check_data_output_pr
791
792
793
794 SUBROUTINE user_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
795
796!------------------------------------------------------------------------------!
797!
798! Description:
799! ------------
800! Set the grids on which user-defined output quantities are defined.
801! Allowed values for grid_x are "x" and "xu", for grid_y "y" and "yv", and
802! for grid_z "zu" and "zw".
803!------------------------------------------------------------------------------!
804
805    USE user
806
807    IMPLICIT NONE
808
809    CHARACTER (LEN=*) ::  grid_x, grid_y, grid_z, variable
810
811    LOGICAL ::  found
812
813
814    SELECT CASE ( TRIM( variable ) )
815
816!
817!--    Uncomment and extend the following lines, if necessary
818!       CASE ( 'u2', 'u2_xy', 'u2_xz', 'u2_yz' )
819!          grid_x = 'xu'
820!          grid_y = 'y'
821!          grid_z = 'zu'
822
823       CASE DEFAULT
824          found  = .FALSE.
825          grid_x = 'none'
826          grid_y = 'none'
827          grid_z = 'none'
828
829    END SELECT
830
831
832 END SUBROUTINE user_define_netcdf_grid
833
834
835
836 SUBROUTINE user_data_output_dvrp( output_variable, local_pf )
837
838!------------------------------------------------------------------------------!
839!
840! Description:
841! ------------
842! Execution of user-defined dvrp output
843!------------------------------------------------------------------------------!
844
845    USE control_parameters
846    USE indices
847    USE pegrid
848    USE user
849
850    IMPLICIT NONE
851
852    CHARACTER (LEN=*) ::  output_variable
853
854    INTEGER ::  i, j, k
855
856    REAL, DIMENSION(nxl:nxr+1,nys:nyn+1,nzb:nz_do3d) ::  local_pf
857
858!
859!-- Here the user-defined DVRP output follows:
860
861!
862!-- Move original array to intermediate array
863    SELECT CASE ( output_variable )
864
865!       CASE ( 'u2', 'u2_xy', 'u2_xz', 'u2_yz',  )
866!!
867!!--       Here the user can add user_defined output quantities.
868!!--       Uncomment and extend the following lines, if necessary.
869!          DO  i = nxl, nxr+1
870!             DO  j = nys, nyn+1
871!                DO  k = nzb, nz_do3d
872!                   local_pf(i,j,k) = u2(k,j,i)
873!                ENDDO
874!             ENDDO
875!          ENDDO
876
877
878       CASE DEFAULT
879!
880!--       The DEFAULT case is reached if output_variable contains a
881!--       wrong character string that is neither recognized in data_output_dvrp
882!--       nor here in user_data_output_dvrp.
883          IF ( myid == 0 )  THEN
884             PRINT*,'+++ (user_)data_output_dvrp: no output possible for: ', &
885                  output_variable
886          ENDIF
887
888    END SELECT
889
890
891 END SUBROUTINE user_data_output_dvrp
892
893
894
895 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf )
896
897!------------------------------------------------------------------------------!
898!
899! Description:
900! ------------
901! Resorts the user-defined output quantity with indices (k,j,i) to a
902! temporary array with indices (i,j,k) and sets the grid on which it is defined.
903! Allowed values for grid are "zu" and "zw".
904!------------------------------------------------------------------------------!
905
906    USE indices
907    USE user
908
909    IMPLICIT NONE
910
911    CHARACTER (LEN=*) ::  grid, variable
912
913    INTEGER ::  av, i, j, k
914
915    LOGICAL ::  found
916
917    REAL, DIMENSION(nxl-1:nxr+1,nys-1:nyn+1,nzb:nzt+1) ::  local_pf
918
919
920    found = .TRUE.
921
922    SELECT CASE ( TRIM( variable ) )
923
924!
925!--    Uncomment and extend the following lines, if necessary.
926!--    The arrays for storing the user defined quantities (here u2 and u2_av)
927!--    have to be declared and defined by the user!
928!--    Sample for user-defined output:
929!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
930!          IF ( av == 0 )  THEN
931!             DO  i = nxl-1, nxr+1
932!                DO  j = nys-1, nyn+1
933!                   DO  k = nzb, nzt+1
934!                      local_pf(i,j,k) = u2(k,j,i)
935!                   ENDDO
936!                ENDDO
937!             ENDDO
938!          ELSE
939!             DO  i = nxl-1, nxr+1
940!                DO  j = nys-1, nyn+1
941!                   DO  k = nzb, nzt+1
942!                      local_pf(i,j,k) = u2_av(k,j,i)
943!                   ENDDO
944!                ENDDO
945!             ENDDO
946!          ENDIF
947!
948!          grid = 'zu'
949
950       CASE DEFAULT
951          found = .FALSE.
952          grid  = 'none'
953
954    END SELECT
955
956
957 END SUBROUTINE user_data_output_2d
958
959
960
961 SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nz_do )
962
963!------------------------------------------------------------------------------!
964!
965! Description:
966! ------------
967! Resorts the user-defined output quantity with indices (k,j,i) to a
968! temporary array with indices (i,j,k) and sets the grid on which it is defined.
969! Allowed values for grid are "zu" and "zw".
970!------------------------------------------------------------------------------!
971
972    USE array_kind
973    USE indices
974    USE user
975
976    IMPLICIT NONE
977
978    CHARACTER (LEN=*) ::  variable
979
980    INTEGER ::  av, i, j, k, nz_do
981
982    LOGICAL ::  found
983
984    REAL(spk), DIMENSION(nxl-1:nxr+1,nys-1:nyn+1,nzb:nz_do) ::  local_pf
985
986
987    found = .TRUE.
988
989    SELECT CASE ( TRIM( variable ) )
990
991!
992!--    Uncomment and extend the following lines, if necessary.
993!--    The arrays for storing the user defined quantities (here u2 and u2_av)
994!--    have to be declared and defined by the user!
995!--    Sample for user-defined output:
996!       CASE ( 'u2' )
997!          IF ( av == 0 )  THEN
998!             DO  i = nxl-1, nxr+1
999!                DO  j = nys-1, nyn+1
1000!                   DO  k = nzb, nz_do
1001!                      local_pf(i,j,k) = u2(k,j,i)
1002!                   ENDDO
1003!                ENDDO
1004!             ENDDO
1005!          ELSE
1006!             DO  i = nxl-1, nxr+1
1007!                DO  j = nys-1, nyn+1
1008!                   DO  k = nzb, nz_do
1009!                      local_pf(i,j,k) = u2_av(k,j,i)
1010!                   ENDDO
1011!                ENDDO
1012!             ENDDO
1013!          ENDIF
1014!
1015!          grid = 'zu'
1016
1017       CASE DEFAULT
1018          found = .FALSE.
1019
1020    END SELECT
1021
1022
1023 END SUBROUTINE user_data_output_3d
1024
1025
1026
1027 SUBROUTINE user_3d_data_averaging( mode, variable )
1028
1029!------------------------------------------------------------------------------!
1030!
1031! Description:
1032! ------------
1033! Sum up and time-average user-defined output quantities as well as allocate
1034! the array necessary for storing the average.
1035!------------------------------------------------------------------------------!
1036
1037    USE control_parameters
1038    USE indices
1039    USE user
1040
1041    IMPLICIT NONE
1042
1043    CHARACTER (LEN=*) ::  mode, variable
1044
1045    INTEGER ::  i, j, k
1046
1047
1048    IF ( mode == 'allocate' )  THEN
1049
1050       SELECT CASE ( TRIM( variable ) )
1051
1052!
1053!--       Uncomment and extend the following lines, if necessary.
1054!--       The arrays for storing the user defined quantities (here u2_av) have
1055!--       to be declared and defined by the user!
1056!--       Sample for user-defined output:
1057!          CASE ( 'u2' )
1058!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
1059!                ALLOCATE( u2_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
1060!             ENDIF
1061!             u2_av = 0.0
1062
1063          CASE DEFAULT
1064             CONTINUE
1065
1066       END SELECT
1067
1068    ELSEIF ( mode == 'sum' )  THEN
1069
1070       SELECT CASE ( TRIM( variable ) )
1071
1072!
1073!--       Uncomment and extend the following lines, if necessary.
1074!--       The arrays for storing the user defined quantities (here u2 and
1075!--       u2_av) have to be declared and defined by the user!
1076!--       Sample for user-defined output:
1077!          CASE ( 'u2' )
1078!             DO  i = nxl-1, nxr+1
1079!                DO  j = nys-1, nyn+1
1080!                   DO  k = nzb, nzt+1
1081!                      u2_av(k,j,i) = u2_av(k,j,i) + u2(k,j,i)
1082!                   ENDDO
1083!                ENDDO
1084!             ENDDO
1085
1086          CASE DEFAULT
1087             CONTINUE
1088
1089       END SELECT
1090
1091    ELSEIF ( mode == 'average' )  THEN
1092
1093       SELECT CASE ( TRIM( variable ) )
1094
1095!
1096!--       Uncomment and extend the following lines, if necessary.
1097!--       The arrays for storing the user defined quantities (here u2_av) have
1098!--       to be declared and defined by the user!
1099!--       Sample for user-defined output:
1100!          CASE ( 'u2' )
1101!             DO  i = nxl-1, nxr+1
1102!                DO  j = nys-1, nyn+1
1103!                   DO  k = nzb, nzt+1
1104!                      u2_av(k,j,i) = u2_av(k,j,i) / REAL( average_count_3d )
1105!                   ENDDO
1106!                ENDDO
1107!             ENDDO
1108
1109       END SELECT
1110
1111    ENDIF
1112
1113
1114 END SUBROUTINE user_3d_data_averaging
Note: See TracBrowser for help on using the repository browser.