Ignore:
Timestamp:
Mar 6, 2007 12:28:36 PM (17 years ago)
Author:
raasch
Message:

preliminary version, several changes to be explained later

File:
1 edited

Legend:

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

    r46 r48  
    55! -----------------
    66! New routine user_init_3d_model which allows the initial setting of all 3d
    7 ! arrays under control of the user
     7! arrays under control of the user,
     8! routine user_statistics now has one argument (sr),
     9! sample for generating time series quantities added
    810!
    911! Former revisions:
     
    174176!       ENDDO
    175177!    ENDIF
     178
     179!
     180!-- Sample for user-defined time series
     181!-- For each time series quantity you have to give a label and a unit,
     182!-- which will be used for the NetCDF file. They must not contain more than
     183!-- seven characters. The value of dots_num has to be increased by the
     184!-- number of new time series quantities. Its old value has to be store in
     185!-- dots_num_palm. See routine user_statistics on how to output calculate
     186!-- and output these quantities.
     187!    dots_label(dots_num+1) = 'abs_umx'
     188!    dots_unit(dots_num+1)  = 'm/s'
     189!    dots_label(dots_num+2) = 'abs_vmx'
     190!    dots_unit(dots_num+2)  = 'm/s'
     191!
     192!    dots_num_palm = dots_num
     193!    dots_num = dots_num + 2
    176194
    177195 END SUBROUTINE user_init
     
    421439
    422440
    423  SUBROUTINE user_statistics
     441 SUBROUTINE user_statistics( sr )
    424442
    425443!------------------------------------------------------------------------------!
     
    428446! ------------
    429447! Calculation of user-defined statistics
     448! This routine is called for every statistic region sr defined by the user,
     449! but at least for the region "total domain" (sr=0).
    430450!------------------------------------------------------------------------------!
    431451
     
    435455    IMPLICIT NONE
    436456
     457    INTEGER ::  sr
     458
     459!
     460!-- Sample on how to add values for the user-defined time series quantities.
     461!-- These have to be defined before in routine user_init. This sample
     462!-- creates two time series for the absolut values of the horizontal
     463!-- velocities u and v.
     464!    ts_value(dots_num_palm+1,sr) = ABS( u_max )
     465!    ts_value(dots_num_palm+2,sr) = ABS( v_max )
    437466
    438467 END SUBROUTINE user_statistics
Note: See TracChangeset for help on using the changeset viewer.