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

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

preliminary update of further changes, advec_particles is not running!

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