source: palm/tags/release-3.3/SOURCE/user_interface.f90 @ 141

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

updating comments and rc-file

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