source: palm/trunk/SOURCE/data_log.f90 @ 4598

Last change on this file since 4598 was 4559, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1!> @file data_log.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 terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: data_log.f90 4559 2020-06-11 08:51:48Z suehring $
26! file re-formatted to follow the PALM coding standard
27!
28! 4360 2020-01-07 11:25:50Z suehring
29! Corrected "Former revisions" section
30!
31! 3725 2019-02-07 10:11:02Z raasch
32! preprocessor directives removed to avoid compiler warnings
33!
34! 3655 2019-01-07 16:51:22Z knoop
35! Corrected "Former revisions" section
36!
37! Revision 1.1  2006/02/23 10:09:29  raasch
38! Initial revision
39!
40!
41! Description:
42! ------------
43!> Complete logging of data
44!--------------------------------------------------------------------------------------------------!
45 SUBROUTINE data_log( array, i1, i2, j1, j2, k1, k2 )
46
47    USE control_parameters,                                                                        &
48        ONLY:  log_message, simulated_time
49
50    USE kinds
51
52    USE pegrid
53
54    IMPLICIT NONE
55
56    INTEGER(iwp) ::  i1  !<
57    INTEGER(iwp) ::  i2  !<
58    INTEGER(iwp) ::  j1  !<
59    INTEGER(iwp) ::  j2  !<
60    INTEGER(iwp) ::  k1  !<
61    INTEGER(iwp) ::  k2  !<
62
63    REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !<
64
65
66!
67!-- Open the file for data logging
68    CALL check_open( 20 )
69
70!
71!-- Write the message string
72    WRITE ( 20 )  log_message
73
74!
75!-- Write the simulated time and the array indices
76    WRITE ( 20 )  simulated_time, i1, i2, j1, j2, k1, k2
77
78!
79!-- Write the array
80    WRITE ( 20 )  array
81
82 END SUBROUTINE data_log
83
84
85
86!--------------------------------------------------------------------------------------------------!
87! Description:
88! ------------
89!> Complete logging of data for 2d arrays
90!--------------------------------------------------------------------------------------------------!
91
92 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
93
94    USE control_parameters,                                                                        &
95        ONLY:  log_message, simulated_time
96
97    USE kinds
98
99    USE pegrid
100
101    IMPLICIT NONE
102
103    INTEGER(iwp) ::  i1  !<
104    INTEGER(iwp) ::  i2  !<
105    INTEGER(iwp) ::  j1  !<
106    INTEGER(iwp) ::  j2  !<
107
108    REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !<
109
110
111!
112!-- Open the file for data logging
113    CALL check_open( 20 )
114
115!
116!-- Write the message string
117    WRITE ( 20 )  log_message
118
119!
120!-- Write the simulated time and the array indices
121    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
122
123!
124!-- Write the array
125    WRITE ( 20 )  array
126
127 END SUBROUTINE data_log_2d
128
129
130
131!--------------------------------------------------------------------------------------------------!
132! Description:
133! ------------
134!> Complete logging of data for 2d integer arrays
135!--------------------------------------------------------------------------------------------------!
136
137 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
138
139    USE control_parameters,                                                                        &
140        ONLY:  log_message, simulated_time
141
142    USE kinds
143
144    USE pegrid
145
146    IMPLICIT NONE
147
148    INTEGER(iwp) ::  i1  !<
149    INTEGER(iwp) ::  i2  !<
150    INTEGER(iwp) ::  j1  !<
151    INTEGER(iwp) ::  j2  !<
152
153    INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !<
154
155
156!
157!-- Open the file for data logging
158    CALL check_open( 20 )
159
160!
161!-- Write the message string
162    WRITE ( 20 )  log_message
163
164!
165!-- Write the simulated time and the array indices
166    WRITE ( 20 )  simulated_time, i1, i2, j1, j2
167
168!
169!-- Write the array
170    WRITE ( 20 )  array
171
172 END SUBROUTINE data_log_2d_int
Note: See TracBrowser for help on using the repository browser.