Ignore:
Timestamp:
Jan 4, 2008 4:29:45 AM (16 years ago)
Author:
letzel
Message:

User-defined spectra.

Bugfix: extra '*' removed in user_statistics sample code (user_interface).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/user_interface.f90

    r139 r144  
    44! Actual revisions:
    55! -----------------
    6 !
     6! new subroutine user_spectra
    77!
    88! Former revisions:
     
    5656!-- Sample for user-defined output
    5757!    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  u2, u2_av
     58!    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  ustvst
    5859
    5960    SAVE
     
    198199!-- Sample for user-defined output
    199200!    ALLOCATE( u2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
     201!    ALLOCATE( ustvst(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
    200202!
    201203!    IF ( initializing_actions == 'read_restart_data' )  THEN
     
    456458!                ENDDO
    457459!             ENDDO
     460!             DO  i = nxl-1, nxr+1
     461!                DO  j = nys-1, nyn+1
     462!                   DO  k = nzb, nzt+1
     463!                      ustvst(k,j,i) =  &
     464!                         ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * &
     465!                         ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
     466!                   ENDDO
     467!                ENDDO
     468!             ENDDO
    458469
    459470
     
    561572 END MODULE user_actions_mod
    562573
     574
     575
     576 SUBROUTINE user_spectra( mode, m, pr )
     577
     578!------------------------------------------------------------------------------!
     579!
     580! Description:
     581! ------------
     582! Calculation of user-defined spectra.
     583! See section 3.5.4 on how to define, calculate, and output user defined
     584! quantities.
     585!------------------------------------------------------------------------------!
     586
     587    USE arrays_3d
     588    USE indices
     589    USE spectrum
     590    USE statistics
     591    USE user
     592
     593    IMPLICIT NONE
     594
     595    CHARACTER (LEN=*) ::  mode
     596
     597    INTEGER ::  i, j, k, m, pr
     598
     599
     600!
     601!-- Sample on how to calculate spectra of user-defined quantities.
     602!-- Each quantity is identified by the corresponding user profile index
     603!-- "pr_palm+#" where "#" is an integer starting from 1. These
     604!-- user-profile-numbers must also be assigned to the respective strings
     605!-- given by data_output_pr_user in routine user_check_data_output_pr.
     606    IF ( mode == 'preprocess' )  THEN
     607
     608       SELECT CASE ( TRIM( data_output_sp(m) ) )
     609         
     610          CASE ( 'u', 'v', 'w', 'pt', 'q' )
     611!--          Not allowed here since these are the standard quantities used in
     612!--          preprocess_spectra.
     613       
     614!          CASE ( 'u*v*' )
     615!             pr = pr_palm+1
     616!             d(nzb+1:nzt,nys:nyn,nxl:nxr) = ustvst(nzb+1:nzt,nys:nyn,nxl:nxr)
     617       
     618          CASE DEFAULT
     619             PRINT*, '+++ user_spectra/preprocess: Spectra of ', &
     620                  TRIM( data_output_sp(m) ), ' can not be calculated'
     621         
     622       END SELECT
     623
     624    ELSEIF ( mode == 'data_output' )  THEN
     625
     626       SELECT CASE ( TRIM( data_output_sp(m) ) )
     627
     628          CASE ( 'u', 'v', 'w', 'pt', 'q' )
     629!--          Not allowed here since these are the standard quantities used in
     630!--          data_output_spectra.
     631
     632!          CASE ( 'u*v*' )
     633!             pr = 6
     634
     635          CASE DEFAULT
     636             PRINT*, '+++ user_spectra/data_output: Spectra of ', &
     637                          TRIM( data_output_sp(m) ), ' are not defined'
     638
     639          END SELECT
     640
     641    ENDIF
     642
     643 END SUBROUTINE user_spectra
    563644
    564645
     
    600681!       DO  i = nxl, nxr
    601682!          DO  j = nys, nyn
    602 !             DO  k = nzb_s_outer(j,i)+1, nzt
     683!             DO  k = nzb_s_inner(j,i)+1, nzt
    603684!!
    604685!!--             Sample on how to calculate the profile of the resolved-scale
     
    606687!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +           &
    607688!                      ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) * &
    608 !                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) * &
     689!                      ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )   &
    609690!                                                 * rmask(j,i,sr)
    610691!!
     
    796877!--    Uncomment and extend the following lines, if necessary
    797878!       CASE ( 'u2' )
     879!          unit = 'm2/s2'
     880!
     881!       CASE ( 'u*v*' )
    798882!          unit = 'm2/s2'
    799883!
     
    890974!       CASE ( 'u2', 'u2_xy', 'u2_xz', 'u2_yz' )
    891975!          grid_x = 'xu'
     976!          grid_y = 'y'
     977!          grid_z = 'zu'
     978
     979!       CASE ( 'u*v*', 'u*v*_xy', 'u*v*_xz', 'u*v*_yz' )
     980!          grid_x = 'x'
    892981!          grid_y = 'y'
    893982!          grid_z = 'zu'
Note: See TracChangeset for help on using the changeset viewer.