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

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

small bugfixes

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