Ignore:
Timestamp:
Oct 24, 2018 6:39:32 PM (5 years ago)
Author:
gronemeier
Message:

new surface-data output; renamed output variables (pt to theta, rho_air to rho, rho_ocean to rho_sea_water)

File:
1 edited

Legend:

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

    r3355 r3421  
    2525! -----------------
    2626! $Id$
     27! Renamed output variables
     28! +surface_data_output
     29!
     30! 3355 2018-10-16 14:03:34Z knoop
    2731! (from branch resler)
    2832! Increase dimension of uv_heights etc.
     
    13531357    LOGICAL ::  sloping_surface = .FALSE.                        !< use sloped surface? (namelist parameter alpha_surface)
    13541358    LOGICAL ::  spinup = .FALSE.                                 !< perform model spinup without atmosphere code?
     1359    LOGICAL ::  surface_data_output = .FALSE.                    !< output of surface data
    13551360    LOGICAL ::  stop_dt = .FALSE.                                !< internal switch to stop the time stepping
    13561361    LOGICAL ::  synchronous_exchange = .FALSE.                   !< namelist parameter
     
    20272032    INTEGER(iwp), PARAMETER ::  crmax = 100  !< maximum number of coordinate systems for profile output
    20282033
    2029     CHARACTER (LEN=20), DIMENSION(20) ::  cross_ts_profiles = &  !< time series to be plotted into one coordinate system, respectively
    2030                            (/ ' E E*               ', ' dt                 ', &
    2031                               ' u* w*              ', ' th*                ', &
    2032                               ' umax vmax wmax     ', ' div_old div_new    ', &
    2033                               ' z_i_wpt z_i_pt     ', ' w"pt"0 w"pt" wpt   ', &
    2034                               ' pt(0) pt(zp)       ', ' splux spluy spluz  ', &
    2035                               ' L                  ',                         &
    2036                             ( '                    ', i9 = 1, 9 ) /)
     2034    CHARACTER (LEN=27), DIMENSION(20) ::  cross_ts_profiles = &  !< time series to be plotted into one coordinate system, respectively
     2035                           (/ ' E E*                      ', &
     2036                              ' dt                        ', &
     2037                              ' u* w*                     ', &
     2038                              ' th*                       ', &
     2039                              ' umax vmax wmax            ', &
     2040                              ' div_old div_new           ', &
     2041                              ' zi_wtheta zi_theta        ', &
     2042                              ' w"theta"0 w"theta" wtheta ', &
     2043                              ' theta(0) theta(zp)        ', &
     2044                              ' splux spluy spluz         ', &
     2045                              ' L                         ', &
     2046                            ( '                           ', i9 = 1, 9 ) /)
    20372047
    20382048    CHARACTER (LEN=100), DIMENSION(crmax) ::  cross_profiles = &  !< quantities to be plotted into one coordinate system, respectively
    2039                            (/ ' u v                           ', &
    2040                               ' pt                            ', &
    2041                               ' w"pt" w*pt* w*pt*BC wpt wptBC ', &
    2042                               ' w"u" w*u* wu w"v" w*v* wv     ', &
    2043                               ' km kh                         ', &
    2044                               ' l                             ', &
     2049                          (/ ' u v                                          ', &
     2050                             ' pt                                           ', &
     2051                             ' w"theta" w*theta* w*theta*BC wtheta wthetaBC ', &
     2052                             ' w"u" w*u* wu w"v" w*v* wv                    ', &
     2053                             ' km kh                                        ', &
     2054                             ' l                                            ', &
    20452055                         ( '                               ', i9 = 1, 94 ) /)
    20462056
Note: See TracChangeset for help on using the changeset viewer.