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

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

Id keyword set as property for all *.f90 files

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