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

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

further changes concerning user-defined profiles

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