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

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

bugs in check_open and user_interface removed

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