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

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

Removed bugfix in exchange_horiz_2d_int().

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