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

Last change on this file since 584 was 584, checked in by heinze, 13 years ago

last commit documented

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