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

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

preparations for the next release

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