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

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

updating parts of Marcus changes

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