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

Last change on this file since 583 was 583, checked in by heinze, 14 years ago

Bugfix: replace 'user_spectra' with 'user_read_restart_data' in call of message

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