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

Last change on this file since 138 was 138, checked in by letzel, 16 years ago

Plant canopy model of Watanabe (2004,BLM 112,307-341) added.

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