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

Last change on this file since 258 was 258, checked in by heinze, 15 years ago

Output of messages replaced by message handling routine.

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