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

Last change on this file since 87 was 87, checked in by raasch, 17 years ago

Preliminary update for user defined profiles

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