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

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

Initial repository layout and content

File size: 21.5 KB
Line 
1 MODULE user
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: user_interface.f90,v $
11! Revision 1.18  2006/06/02 15:25:00  raasch
12! +change of grid-defining arguments in routine user_define_netcdf_grid,
13! new argument "found" in user_data_output_2d and user_data_output_3d
14!
15! Revision 1.17  2006/04/11 14:59:28  raasch
16! Reading and writing user-defined quantities from/to the restart file improved
17!
18! Revision 1.16  2006/03/03 20:00:48  raasch
19! Error removed from last version
20!
21! Revision 1.15  2006/03/03 19:55:36  raasch
22! Call of user_init_grid now requires the formal parameter nzb_local
23!
24! Revision 1.14  2006/02/23 13:13:18  raasch
25! Additional interfaces for the calculation and output of user-defined 2d- and
26! 3d-data
27!
28! Revision 1.13  2003/03/12 16:44:56  raasch
29! Full code replaced in routine user_actions (in the call for all gridpoints)
30! instead of calling the _ij version (required by NEC, because otherwise no
31! vectorization)
32!
33! Revision 1.12  2002/12/19 16:22:04  raasch
34! SAVE added in module user, STOP statement replaced by call of subroutine
35! local_stop
36!
37! Revision 1.11  2002/06/11 13:22:09  raasch
38! Former subroutine changed to a module which allows to be called for all grid
39! points of a single vertical column with index i,j or for all grid points by
40! using function overloading.
41! Log point for user_actions removed from the grid point version.
42!
43! Revision 1.10  2001/08/21 12:13:55  raasch
44! Wrong module in user_actions changed
45!
46! Revision 1.9  2001/08/21 10:04:30  raasch
47! User_actions can be called from every prognostic equation,
48! subroutine user_statistics, user_particle_attributes, user_dvrp_coltab added
49!
50! Revision 1.8  2001/07/12 12:45:07  raasch
51! Subroutine user_init_particles added
52!
53! Revision 1.7  2001/03/30 07:58:52  raasch
54! Translation of remaining German identifiers (variables, subroutines, etc.)
55!
56! Revision 1.6  2000/08/07 12:43:16  raasch
57! All comments translated into English
58!
59! Revision 1.5  1998/04/06 14:42:21  raasch
60! +SUBROUTINE user_last_actions
61!
62! Revision 1.4  1998/03/30 11:38:37  raasch
63! Fehlerkorrekturen und Ausgabeaenderungen
64!
65! Revision 1.3  1998/03/25 20:11:17  raasch
66! +region in userpar
67!
68! Revision 1.2  1998/03/25 13:57:37  raasch
69! userpar beinhaltet jetzt keine vordefinierten Variablen mehr
70!
71! Revision 1.1  1998/03/24 15:29:04  raasch
72! Initial revision
73!
74!
75! Description:
76! ------------
77! Declaration of user-defined variables. This module may only be used
78! in the user-defined routines (contained in user_interface.f90).
79!------------------------------------------------------------------------------!
80
81    INTEGER ::  user_idummy
82    LOGICAL ::  user_defined_namelist_found = .FALSE.
83    REAL    ::  user_dummy
84
85!
86!-- Sample for user-defined output
87!    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  u2, u2_av
88
89    SAVE
90
91 END MODULE user
92
93
94 SUBROUTINE user_parin
95
96!------------------------------------------------------------------------------!
97!
98! Description:
99! ------------
100! Interface to read user-defined namelist-parameters.
101!------------------------------------------------------------------------------!
102
103    USE control_parameters
104    USE statistics
105    USE user
106
107    IMPLICIT NONE
108
109    CHARACTER (LEN=80) ::  zeile
110
111
112    NAMELIST /userpar/  data_output_user, region
113
114!
115!-- Position the namelist-file at the beginning (it was already opened in
116!-- parin), search for user-defined namelist-group ("userpar", but any other
117!-- name can be choosed) and position the file at this line.
118    REWIND ( 11 )
119
120    zeile = ' '
121    DO   WHILE ( INDEX( zeile, '&userpar' ) == 0 )
122       READ ( 11, '(A)', END=100 )  zeile
123    ENDDO
124    BACKSPACE ( 11 )
125
126!
127!-- Read user-defined namelist
128    READ ( 11, userpar )
129    user_defined_namelist_found = .TRUE.
130
131100 RETURN
132
133 END SUBROUTINE user_parin
134
135
136
137 SUBROUTINE user_header( io )
138
139!------------------------------------------------------------------------------!
140!
141! Description:
142! ------------
143! Print a header with user-defined informations.
144!------------------------------------------------------------------------------!
145
146    USE statistics
147    USE user
148
149    IMPLICIT NONE
150
151    INTEGER ::  i, io
152
153!
154!-- If no user-defined variables are read from the namelist-file, no
155!-- informations will be printed.
156    IF ( .NOT. user_defined_namelist_found )  THEN
157       WRITE ( io, 100 )
158       RETURN
159    ENDIF
160
161!
162!-- Printing the informations.
163    WRITE ( io, 110 )
164
165    IF ( statistic_regions /= 0 )  THEN
166       WRITE ( io, 200 )
167       DO  i = 0, statistic_regions
168          WRITE ( io, 201 )  i, region(i)
169       ENDDO
170    ENDIF
171
172
173
174!
175!-- Format-descriptors
176100 FORMAT (//' *** no user-defined variables found'/)
177110 FORMAT (//1X,78('#')                                      &
178            //' User-defined variables and actions:'/  &
179              ' -----------------------------------'//)
180200 FORMAT (' Output of profiles and time series for following regions:' /)
181201 FORMAT (4X,'Region ',I1,':   ',A)
182
183
184 END SUBROUTINE user_header
185
186
187
188 SUBROUTINE user_init
189
190!------------------------------------------------------------------------------!
191!
192! Description:
193! ------------
194! Execution of user-defined initializing actions
195!------------------------------------------------------------------------------!
196
197    USE control_parameters
198    USE indices
199    USE pegrid
200    USE user
201
202    IMPLICIT NONE
203
204    CHARACTER (LEN=20) :: field_char
205!
206!-- Here the user-defined initializing actions follow:
207!-- Sample for user-defined output
208!    ALLOCATE( u2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
209!
210!    IF ( initializing_actions == 'read_restart_data' )  THEN
211!       READ ( 13 )  field_chr
212!       DO  WHILE ( TRIM( field_chr ) /= '*** end user ***' )
213!
214!          SELECT CASE ( TRIM( field_chr ) )
215!
216!             CASE ( 'u2_av' )
217!                ALLOCATE( u2_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
218!                READ ( 13 )  u2_av
219!
220!             CASE DEFAULT
221!                PRINT*, '+++ user_init: unknown variable named "', &
222!                        TRIM( field_chr ), '" found in'
223!                PRINT*, '               data from prior run on PE ', myid
224!                CALL local_stop
225!
226!          END SELECT
227!       ENDDO
228!    ENDIF
229
230 END SUBROUTINE user_init
231
232
233
234 SUBROUTINE user_init_grid( nzb_local )
235
236!------------------------------------------------------------------------------!
237!
238! Description:
239! ------------
240! Execution of user-defined grid initializing actions
241!------------------------------------------------------------------------------!
242
243    USE control_parameters
244    USE indices
245    USE user
246
247    IMPLICIT NONE
248
249    INTEGER, DIMENSION(-1:ny+1,-1:nx+1) ::  nzb_local
250
251!
252!-- Here the user-defined grid initializing actions follow:
253
254!
255!-- Set the index array nzb_local for non-flat topography.
256!-- Here consistency checks concerning domain size and periodicity are necessary
257    SELECT CASE ( TRIM( topography ) )
258
259       CASE ( 'flat', 'single_building' )
260!
261!--       Not allowed here since these are the standard cases used in init_grid.
262
263       CASE ( 'user_defined_topography_1' )
264!
265!--       Here the user can define his own topography. After definition, please
266!--       remove the following three lines!
267          PRINT*, '+++ user_init_grid: topography "', &
268               topography, '" not available yet'
269          CALL local_stop
270
271       CASE DEFAULT
272!
273!--       The DEFAULT case is reached if the parameter topography contains a
274!--       wrong character string that is neither recognized in init_grid nor
275!--       here in user_init_grid.
276          PRINT*, '+++ (user_)init_grid: unknown topography "', &
277               topography, '"'
278          CALL local_stop
279
280    END SELECT
281
282
283 END SUBROUTINE user_init_grid
284
285
286
287 MODULE user_actions_mod
288
289!------------------------------------------------------------------------------!
290!
291! Description:
292! ------------
293! Execution of user-defined actions before or after single timesteps
294!------------------------------------------------------------------------------!
295
296    PRIVATE
297    PUBLIC user_actions
298
299    INTERFACE user_actions
300       MODULE PROCEDURE user_actions
301       MODULE PROCEDURE user_actions_ij
302    END INTERFACE user_actions
303
304 CONTAINS
305
306
307!------------------------------------------------------------------------------!
308! Call for all grid points
309!------------------------------------------------------------------------------!
310    SUBROUTINE user_actions( location )
311
312       USE control_parameters
313       USE cpulog
314       USE indices
315       USE interfaces
316       USE pegrid
317       USE user
318       USE arrays_3d
319
320       IMPLICIT NONE
321
322       CHARACTER (LEN=*) ::  location
323
324       INTEGER ::  i, j, k
325
326       CALL cpu_log( log_point(24), 'user_actions', 'start' )
327
328!
329!--    Here the user-defined actions follow
330!--    No calls for single grid points are allowed at locations before and
331!--    after the timestep, since these calls are not within an i,j-loop
332       SELECT CASE ( location )
333
334          CASE ( 'before_timestep' )
335!
336!--          Enter actions to be done before every timestep here
337
338
339          CASE ( 'after_integration' )
340!
341!--          Enter actions to be done after every time integration (before
342!--          data output)
343!--          Sample for user-defined output:
344!             DO  i = nxl-1, nxr+1
345!                DO  j = nys-1, nyn+1
346!                   DO  k = nzb, nzt+1
347!                      u2(k,j,i) = u(k,j,i)**2
348!                   ENDDO
349!                ENDDO
350!             ENDDO
351
352
353          CASE ( 'after_timestep' )
354!
355!--          Enter actions to be done after every timestep here
356
357
358          CASE ( 'u-tendency' )
359!
360!--          Enter actions to be done in the u-tendency term here
361
362
363          CASE ( 'v-tendency' )
364
365
366          CASE ( 'w-tendency' )
367
368
369          CASE ( 'pt-tendency' )
370
371
372          CASE ( 'e-tendency' )
373
374
375          CASE ( 'q-tendency' )
376
377
378          CASE DEFAULT
379             IF ( myid == 0 )  PRINT*, '+++ user_actions: unknown location "', &
380                                       location, '"'
381             CALL local_stop
382
383       END SELECT
384
385       CALL cpu_log( log_point(24), 'user_actions', 'stop' )
386
387    END SUBROUTINE user_actions
388
389
390!------------------------------------------------------------------------------!
391! Call for grid point i,j
392!------------------------------------------------------------------------------!
393    SUBROUTINE user_actions_ij( i, j, location )
394
395       USE control_parameters
396       USE pegrid
397       USE user
398
399       IMPLICIT NONE
400
401       CHARACTER (LEN=*) ::  location
402
403       INTEGER ::  i, idum, j
404
405
406!
407!--    Here the user-defined actions follow
408       SELECT CASE ( location )
409
410          CASE ( 'u-tendency' )
411!
412!--          Enter actions to be done in the u-tendency term here
413
414
415          CASE ( 'v-tendency' )
416
417
418          CASE ( 'w-tendency' )
419
420
421          CASE ( 'pt-tendency' )
422
423
424          CASE ( 'e-tendency' )
425
426
427          CASE ( 'q-tendency' )
428
429
430          CASE ( 'before_timestep', 'after_integration', 'after_timestep' )
431             IF ( myid == 0 )  THEN
432                PRINT*, '+++ user_actions: location "', location, '" is not ', &
433                             'allowed to be called with parameters "i" and "j"'
434             ENDIF
435             CALL local_stop
436
437
438          CASE DEFAULT
439             IF ( myid == 0 )  PRINT*, '+++ user_actions: unknown location "', &
440                                       location, '"'
441             CALL local_stop
442
443
444       END SELECT
445
446    END SUBROUTINE user_actions_ij
447
448 END MODULE user_actions_mod
449
450
451
452 SUBROUTINE user_statistics
453
454!------------------------------------------------------------------------------!
455!
456! Description:
457! ------------
458! Calculation of user-defined statistics
459!------------------------------------------------------------------------------!
460
461    USE statistics
462    USE user
463
464    IMPLICIT NONE
465
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.