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

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

further preliminary uncomplete changes for ocean version

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