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

Last change on this file since 1321 was 1321, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 5.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! This file is part of PALM.
8!
9! PALM is free software: you can redistribute it and/or modify it under the terms
10! of the GNU General Public License as published by the Free Software Foundation,
11! either version 3 of the License, or (at your option) any later version.
12!
13! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
14! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
15! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
16!
17! You should have received a copy of the GNU General Public License along with
18! PALM. If not, see <http://www.gnu.org/licenses/>.
19!
20! Copyright 1997-2014 Leibniz Universitaet Hannover
21!--------------------------------------------------------------------------------!
22!
23! Current revisions:
24! -----------------
25!
26!
27! Former revisions:
28! -----------------
29! $Id: user_read_restart_data.f90 1321 2014-03-20 09:40:40Z raasch $
30!
31! 1320 2014-03-20 08:40:49Z raasch
32! kind-parameters added to all INTEGER and REAL declaration statements,
33! kinds are defined in new module kinds,
34! old module precision_kind is removed,
35! revision history before 2012 removed,
36! comment fields (!:) to be used for variable explanations added to
37! all variable declaration statements
38!
39! 1036 2012-10-22 13:43:42Z raasch
40! code put under GPL (PALM 3.9)
41!
42! 220 2008-12-18 07:00:36Z raasch
43! reading mechanism revised (subdomain/total domain size can vary arbitrarily
44! between current and previous run),
45! former file user_interface.f90 split into one file per subroutine
46!
47! Description:
48! ------------
49! Reading restart data from file(s)
50! Subdomain index limits on file are given by nxl_on_file, etc.
51! Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
52! subdomain on file (f) to the subdomain of the current PE (c). They have been
53! calculated in routine read_3d_binary.
54!------------------------------------------------------------------------------!
55
56    USE control_parameters
57       
58    USE indices
59   
60    USE kinds
61   
62    USE pegrid
63   
64    USE user
65
66    IMPLICIT NONE
67
68    CHARACTER (LEN=20) :: field_char   !:
69
70    INTEGER(iwp) ::  i               !:
71    INTEGER(iwp) ::  k               !:
72    INTEGER(iwp) ::  nxlc            !:
73    INTEGER(iwp) ::  nxlf            !:
74    INTEGER(iwp) ::  nxl_on_file     !:
75    INTEGER(iwp) ::  nxrc            !:
76    INTEGER(iwp) ::  nxrf            !:
77    INTEGER(iwp) ::  nxr_on_file     !:
78    INTEGER(iwp) ::  nync            !:
79    INTEGER(iwp) ::  nynf            !:
80    INTEGER(iwp) ::  nyn_on_file     !:
81    INTEGER(iwp) ::  nysc            !:
82    INTEGER(iwp) ::  nysf            !:
83    INTEGER(iwp) ::  nys_on_file     !:
84    INTEGER(iwp) ::  overlap_count   !:
85
86    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxlfa       !:
87    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxrfa       !:
88    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nynfa       !:
89    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nysfa       !:
90    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_xa   !:
91    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_ya   !:
92
93    REAL(wp),                                                                  &
94       DIMENSION(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) ::&
95          tmp_2d   !:
96
97    REAL(wp),                                                                  &
98       DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) ::&
99          tmp_3d   !:
100
101!
102!-- Here the reading of user-defined restart data follows:
103!-- Sample for user-defined output
104!
105!    IF ( initializing_actions == 'read_restart_data' )  THEN
106!       READ ( 13 )  field_char
107!       DO  WHILE ( TRIM( field_char ) /= '*** end user ***' )
108!
109!          DO  k = 1, overlap_count
110!
111!             nxlf = nxlfa(i,k)
112!             nxlc = nxlfa(i,k) + offset_xa(i,k)
113!             nxrf = nxrfa(i,k)
114!             nxrc = nxrfa(i,k) + offset_xa(i,k)
115!             nysf = nysfa(i,k)
116!             nysc = nysfa(i,k) + offset_ya(i,k)
117!             nynf = nynfa(i,k)
118!             nync = nynfa(i,k) + offset_ya(i,k)
119!
120!
121!             SELECT CASE ( TRIM( field_char ) )
122!
123!                CASE ( 'u2_av' )
124!                   IF ( .NOT. ALLOCATED( u2_av ) ) THEN
125!                      ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
126!                   ENDIF
127!                   IF ( k == 1 )  READ ( 13 )  tmp_3d
128!                   u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
129!                                          tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
130!
131!                CASE DEFAULT
132!                   WRITE( message_string, * ) 'unknown variable named "',       &
133!                                         TRIM( field_char ), '" found in',      &
134!                                         '&data from prior run on PE ', myid
135!                   CALL message( 'user_read_restart_data', 'UI0012', 1, 2, 0, 6, 0 )
136!
137!             END SELECT
138!
139!          ENDDO
140!
141!          READ ( 13 )  field_char
142!
143!       ENDDO
144!    ENDIF
145
146 END SUBROUTINE user_read_restart_data
147
Note: See TracBrowser for help on using the repository browser.