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

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

further updates for turbulent inflow: reading input data of a precursor run using a smaller total domain is working

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