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

Last change on this file since 688 was 668, checked in by suehring, 13 years ago

last commit documented

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