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

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

preliminary version, several changes to be explained later

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