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

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

preliminary updates for implementing buildings in poismg

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