Changeset 144 for palm/trunk/SOURCE


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

User-defined spectra.

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

Location:
palm/trunk/SOURCE
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/CURRENT_MODIFICATIONS

    r143 r144  
    1515necessary for the current subdomain.
    1616
    17 check_open, read_var_list, read_3d_binary, write_3d_binary
     17User-defined spectra.
     18
     19calc_spectra, check_open, data_output_spectra, netcdf, read_var_list, read_3d_binary, user_interface, write_3d_binary
    1820
    1921
     
    3840NetCDF files newly created by restart files (no append of existing files!)
    3941contained uneccessary time levels. (read_3d_binary, write_3d_binary)
     42Bugfix: extra '*' removed in user_statistics sample code (user_interface)
    4043
    41 flow_statistics, plant_canopy_model, read_3d_binary, write_3d_binary
     44flow_statistics, plant_canopy_model, read_3d_binary, user_interface, write_3d_binary
    4245
  • palm/trunk/SOURCE/calc_spectra.f90

    r4 r144  
    44! Actual revisions:
    55! -----------------
    6 !
     6! user-defined spectra
    77!
    88! Former revisions:
     
    180180       
    181181    CASE DEFAULT
    182        PRINT*, '+++ preprocess_spectra: Spectra of ', &
    183                TRIM( data_output_sp(m) ), ' can not be calculated'
     182!
     183!--    The DEFAULT case is reached either if the parameter data_output_sp(m)
     184!--    contains a wrong character string or if the user has coded a special
     185!--    case in the user interface. There, the subroutine user_spectra
     186!--    checks which of these two conditions applies.
     187       CALL user_spectra( 'preprocess', m, pr )
    184188         
    185189    END SELECT
  • palm/trunk/SOURCE/data_output_spectra.f90

    r4 r144  
    44! Actual revisions:
    55! -----------------
    6 !
     6! user-defined spectra
    77!
    88! Former revisions:
     
    117117
    118118             CASE DEFAULT
    119                 PRINT*, '+++ data_output_spectra: Spectra of ', &
    120                              TRIM( data_output_sp(m) ), ' are not defined'
     119!
     120!--             The DEFAULT case is reached either if the parameter
     121!--             data_output_sp(m) contains a wrong character string or if the
     122!--             user has coded a special case in the user interface. There, the
     123!--             subroutine user_spectra checks which of these two conditions
     124!--             applies.
     125                CALL user_spectra( 'data_output', m, pr )
    121126
    122127          END SELECT
  • palm/trunk/SOURCE/netcdf.f90

    r98 r144  
    77! Current revisions:
    88! ------------------
    9 !
     9! user-defined spectra
    1010!
    1111! Former revisions:
     
    28672867          i = 1
    28682868          DO WHILE ( data_output_sp(i) /= ' '  .AND.  i <= 10 )
     2869!
     2870!--          First check for the vertical grid
     2871             found = .TRUE.
     2872             SELECT CASE ( data_output_sp(i) )
     2873!
     2874!--             Most variables are defined on the zu levels
     2875                CASE ( 'e', 'p', 'pc', 'pr', 'pt', 'q', 'ql', 'ql_c', 'ql_v', &
     2876                       'ql_vp', 'qv', 'rho', 's', 'sa', 'u', 'v', 'vpt' )
     2877
     2878                   grid_z = 'zu'
     2879!
     2880!--             zw levels
     2881                CASE ( 'w' )
     2882
     2883                   grid_z = 'zw'
     2884
     2885                CASE DEFAULT
     2886!
     2887!--                Check for user-defined quantities (found, grid_x and grid_y
     2888!--                are dummies)
     2889                   CALL user_define_netcdf_grid( data_output_sp(i), found,  &
     2890                                                 grid_x, grid_y, grid_z )
     2891
     2892             END SELECT
    28692893
    28702894             IF ( INDEX( spectra_direction(i), 'x' ) /= 0 )  THEN
     
    28732897!--             Define the variable
    28742898                netcdf_var_name = TRIM( data_output_sp(i) ) // '_x'
    2875                 IF ( data_output_sp(i) == 'w' )  THEN
     2899                CALL clean_netcdf_varname( netcdf_var_name )
     2900                IF ( TRIM( grid_z ) == 'zw' )  THEN
    28762901                   nc_stat = NF90_DEF_VAR( id_set_sp, netcdf_var_name,      &
    28772902                                           nc_precision(7), (/ id_dim_x_sp, &
     
    29032928!--             Define the variable
    29042929                netcdf_var_name = TRIM( data_output_sp(i) ) // '_y'
    2905                 IF ( data_output_sp(i) == 'w' )  THEN
     2930                CALL clean_netcdf_varname( netcdf_var_name )
     2931                IF ( TRIM( grid_z ) == 'zw' )  THEN
    29062932                   nc_stat = NF90_DEF_VAR( id_set_sp, netcdf_var_name,      &
    29072933                                           nc_precision(7), (/ id_dim_y_sp, &
  • 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.