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

Last change on this file since 145 was 145, checked in by raasch, 16 years ago

second preliminary update for turbulent inflow

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