Ignore:
Timestamp:
Jan 9, 2008 8:17:38 AM (17 years ago)
Author:
raasch
Message:

second preliminary update for turbulent inflow

File:
1 edited

Legend:

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

    r144 r145  
    44! Actual revisions:
    55! -----------------
    6 ! new subroutine user_spectra
     6! +routines user_read_restart_data, user_spectra
    77!
    88! Former revisions:
     
    177177
    178178
    179  SUBROUTINE user_init
    180 
    181 !------------------------------------------------------------------------------!
    182 !
    183 ! Description:
    184 ! ------------
    185 ! Execution of user-defined initializing actions
     179 SUBROUTINE user_read_restart_data
     180
     181!------------------------------------------------------------------------------!
     182!
     183! Description:
     184! ------------
     185! Reading restart data from file(s)
    186186!------------------------------------------------------------------------------!
    187187
    188188    USE control_parameters
    189189    USE indices
    190     USE netcdf_control
    191190    USE pegrid
    192191    USE user
     
    196195    CHARACTER (LEN=20) :: field_char
    197196!
    198 !-- Here the user-defined initializing actions follow:
     197!-- Here the reading of user-defined restart data follows:
    199198!-- Sample for user-defined output
    200199!    ALLOCATE( u2(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
     
    224223!    ENDIF
    225224
    226 !
     225 END SUBROUTINE user_read_restart_data
     226
     227
     228
     229 SUBROUTINE user_init
     230
     231!------------------------------------------------------------------------------!
     232!
     233! Description:
     234! ------------
     235! Execution of user-defined initializing actions
     236!------------------------------------------------------------------------------!
     237
     238    USE control_parameters
     239    USE indices
     240    USE netcdf_control
     241    USE pegrid
     242    USE user
     243
     244    IMPLICIT NONE
     245
     246    CHARACTER (LEN=20) :: field_char
     247!
     248!-- Here the user-defined initializing actions follow:
    227249!-- Sample for user-defined time series
    228250!-- For each time series quantity you have to give a label and a unit,
Note: See TracChangeset for help on using the changeset viewer.