source: palm/trunk/SOURCE/user_read_restart_data_mod.f90 @ 3196

Last change on this file since 3196 was 2894, checked in by Giersch, 6 years ago

Reading/Writing? data in case of restart runs revised

  • Property svn:keywords set to Id
File size: 4.5 KB
Line 
1!> @file user_read_restart_data_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: user_read_restart_data_mod.f90 2894 2018-03-15 09:17:58Z maronga $
27! Initial revision
28!
29!
30! Description:
31! ------------
32!> Reads user specific restart data into binary file(s) for restart runs.
33!------------------------------------------------------------------------------!
34 MODULE user_read_restart_data_mod
35
36
37    USE user
38     
39
40    IMPLICIT NONE
41
42
43    INTERFACE user_rrd_global
44       MODULE PROCEDURE user_rrd_global
45    END INTERFACE user_rrd_global
46
47    INTERFACE user_rrd_local
48       MODULE PROCEDURE user_rrd_local
49    END INTERFACE user_rrd_local
50
51
52    PUBLIC user_rrd_global, user_rrd_local
53
54
55 CONTAINS
56
57
58!-------------
59! Description:
60! ------------
61!> Reading global restart data that has been defined by the user.
62!------------------------------------------------------------------------------!
63    SUBROUTINE user_rrd_global( found )
64
65
66       USE control_parameters,                                                 &
67           ONLY: length, restart_string
68
69
70       IMPLICIT NONE
71
72       LOGICAL, INTENT(OUT)  ::  found 
73
74
75       found = .TRUE.
76
77
78       SELECT CASE ( restart_string(1:length) )
79
80          CASE ( 'global_paramter' )
81!             READ ( 13 )  global_parameter
82
83          CASE DEFAULT
84 
85             found = .FALSE.
86
87       END SELECT 
88
89
90    END SUBROUTINE user_rrd_global
91
92
93! Description:
94! ------------
95!> Reading processor specific restart data from file(s) that has been defined
96!> by the user.
97!> Subdomain index limits on file are given by nxl_on_file, etc.
98!> Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
99!> subdomain on file (f) to the subdomain of the current PE (c). They have been
100!> calculated in routine rrd_local.
101!------------------------------------------------------------------------------!
102    SUBROUTINE user_rrd_local( i, k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,      &
103                               nxr_on_file, nynf, nync, nyn_on_file, nysf,     & 
104                               nysc, nys_on_file, tmp_3d, found )
105   
106
107       USE control_parameters
108           
109       USE indices
110       
111       USE kinds
112       
113       USE pegrid
114 
115
116       IMPLICIT NONE
117
118       INTEGER(iwp) ::  i               !<
119       INTEGER(iwp) ::  k               !<
120       INTEGER(iwp) ::  nxlc            !<
121       INTEGER(iwp) ::  nxlf            !<
122       INTEGER(iwp) ::  nxl_on_file     !<
123       INTEGER(iwp) ::  nxrc            !<
124       INTEGER(iwp) ::  nxrf            !<
125       INTEGER(iwp) ::  nxr_on_file     !<
126       INTEGER(iwp) ::  nync            !<
127       INTEGER(iwp) ::  nynf            !<
128       INTEGER(iwp) ::  nyn_on_file     !<
129       INTEGER(iwp) ::  nysc            !<
130       INTEGER(iwp) ::  nysf            !<
131       INTEGER(iwp) ::  nys_on_file     !<
132
133       LOGICAL, INTENT(OUT)  ::  found 
134
135       REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
136
137!
138!-- Here the reading of user-defined restart data follows:
139!-- Sample for user-defined output
140
141
142       found = .TRUE.
143
144
145          SELECT CASE ( restart_string(1:length) )
146
147             CASE ( 'u2_av' )
148!                IF ( .NOT. ALLOCATED( u2_av ) ) THEN
149!                     ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
150!                ENDIF
151!                IF ( k == 1 )  READ ( 13 )  tmp_3d
152!                   u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
153!                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
154!
155             CASE DEFAULT
156
157                found = .FALSE.
158
159             END SELECT
160
161
162    END SUBROUTINE user_rrd_local
163
164
165 END MODULE user_read_restart_data_mod
Note: See TracBrowser for help on using the repository browser.