source: palm/trunk/SOURCE/user_read_restart_data.f90 @ 211

Last change on this file since 211 was 211, checked in by raasch, 15 years ago

user interface was split into one single file per subroutine

  • Property svn:keywords set to Id
File size: 2.4 KB
Line 
1 SUBROUTINE user_read_restart_data( nxlc, nxlf, nxl_on_file, nxrc, nxrf,  &
2                                    nxr_on_file, nync, nynf, nyn_on_file, &
3                                    nysc, nysf, nys_on_file, tmp_2d, tmp_3d )
4
5!------------------------------------------------------------------------------!
6! Actual revisions:
7! -----------------
8! Former file user_interface.f90 split into one file per subroutine
9!
10! Former revisions:
11! -----------------
12! $Id: user_read_restart_data.f90 211 2008-11-11 04:46:24Z raasch $
13!
14! Description:
15! ------------
16! Reading restart data from file(s)
17! Subdomain index limits on file are given by nxl_on_file, etc.
18! Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
19! subdomain on file (f) to the subdomain of the current PE (c). They have been
20! calculated in routine read_3d_binary.
21!------------------------------------------------------------------------------!
22
23    USE control_parameters
24    USE indices
25    USE pegrid
26    USE user
27
28    IMPLICIT NONE
29
30    CHARACTER (LEN=20) :: field_char
31
32    INTEGER ::  nxlc, nxlf, nxl_on_file, nxrc, nxrf, nxr_on_file, nync, nynf, &
33                nyn_on_file, nysc, nysf, nys_on_file
34
35    REAL, DIMENSION(nys_on_file-1:nyn_on_file+1,nxl_on_file-1:nxr_on_file+1) ::&
36          tmp_2d
37
38    REAL, DIMENSION(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, &
39                    nxl_on_file-1:nxr_on_file+1) ::        &
40          tmp_3d
41
42!
43!-- Here the reading of user-defined restart data follows:
44!-- Sample for user-defined output
45!
46!    IF ( initializing_actions == 'read_restart_data' )  THEN
47!       READ ( 13 )  field_char
48!       DO  WHILE ( TRIM( field_char ) /= '*** end user ***' )
49!
50!          SELECT CASE ( TRIM( field_char ) )
51!
52!             CASE ( 'u2_av' )
53!                IF ( .NOT. ALLOCATED( u2_av ) ) THEN
54!                   ALLOCATE( u2_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
55!                ENDIF
56!                READ ( 13 )  tmp_3d
57!                u2_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = &
58!                                          tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1)
59!
60!             CASE DEFAULT
61!                PRINT*, '+++ user_init: unknown variable named "', &
62!                        TRIM( field_char ), '" found in'
63!                PRINT*, '               data from prior run on PE ', myid
64!                CALL local_stop
65!
66!          END SELECT
67!
68!          READ ( 13 )  field_char
69!
70!       ENDDO
71!    ENDIF
72
73 END SUBROUTINE user_read_restart_data
74
Note: See TracBrowser for help on using the repository browser.